Commit 0e91fff8 authored by Abinaya Sudhir's avatar Abinaya Sudhir

Add Navigation for Tabview

parent 408b6f2a
...@@ -2,7 +2,7 @@ module Navigation where ...@@ -2,7 +2,7 @@ module Navigation where
import DOM import DOM
import Gargantext.Data.Lang import Gargantext.Data.Lang
import Prelude import Prelude hiding (div)
import AddCorpusview as AC import AddCorpusview as AC
import AnnotationDocumentView as D import AnnotationDocumentView as D
...@@ -24,8 +24,11 @@ import React.DOM (a, button, div, footer, form, hr, i, img, input, li, p, span, ...@@ -24,8 +24,11 @@ import React.DOM (a, button, div, footer, form, hr, i, img, input, li, p, span,
import React.DOM.Props (Props, _data, _id, _type, aria, className, href, name, onClick, placeholder, role, src, style, tabIndex, target, title) import React.DOM.Props (Props, _data, _id, _type, aria, className, href, name, onClick, placeholder, role, src, style, tabIndex, target, title)
import React.DOM.Props as RP import React.DOM.Props as RP
import SearchForm as S import SearchForm as S
import Tabview as TV
import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultRender, focus, modifyState, simpleSpec, withState) import Thermite (PerformAction, Render, Spec, _render, cotransform, defaultRender, focus, modifyState, simpleSpec, withState)
import UserPage as UP import UserPage as UP
type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e) type E e = (dom :: DOM, ajax :: AJAX, console :: CONSOLE | e)
type AppState = type AppState =
...@@ -38,6 +41,7 @@ type AppState = ...@@ -38,6 +41,7 @@ type AppState =
, userPage :: UP.State , userPage :: UP.State
, annotationdocumentView :: D.State , annotationdocumentView :: D.State
, ntreeView :: NT.State , ntreeView :: NT.State
, tabview :: TV.State
} }
initAppState :: AppState initAppState :: AppState
...@@ -51,6 +55,7 @@ initAppState = ...@@ -51,6 +55,7 @@ initAppState =
, userPage : UP.initialState , userPage : UP.initialState
, annotationdocumentView : D.initialState , annotationdocumentView : D.initialState
, ntreeView : NT.exampleTree , ntreeView : NT.exampleTree
, tabview : TV.initialState
} }
data Action data Action
...@@ -64,6 +69,7 @@ data Action ...@@ -64,6 +69,7 @@ data Action
| UserPageA UP.Action | UserPageA UP.Action
| AnnotationDocumentViewA D.Action | AnnotationDocumentViewA D.Action
| TreeViewA NT.Action | TreeViewA NT.Action
| TabViewA TV.Action
performAction :: forall eff props. PerformAction ( dom :: DOM performAction :: forall eff props. PerformAction ( dom :: DOM
...@@ -167,6 +173,17 @@ _treeAction = prism TreeViewA \action -> ...@@ -167,6 +173,17 @@ _treeAction = prism TreeViewA \action ->
_-> Left action _-> Left action
_tabviewState :: Lens' AppState TV.State
_tabviewState = lens (\s -> s.tabview) (\s ss -> s {tabview = ss})
_tabviewAction :: Prism' Action TV.Action
_tabviewAction = prism TabViewA \action ->
case action of
TabViewA caction -> Right caction
_-> Left action
pagesComponent :: forall props eff. AppState -> Spec (E eff) AppState props Action pagesComponent :: forall props eff. AppState -> Spec (E eff) AppState props Action
pagesComponent s = pagesComponent s =
case s.currentRoute of case s.currentRoute of
...@@ -186,6 +203,7 @@ pagesComponent s = ...@@ -186,6 +203,7 @@ pagesComponent s =
selectSpec DocView = layout0 $ focus _docViewState _docViewAction DV.layoutDocview selectSpec DocView = layout0 $ focus _docViewState _docViewAction DV.layoutDocview
selectSpec UserPage = layout0 $ focus _userPageState _userPageAction UP.layoutUser selectSpec UserPage = layout0 $ focus _userPageState _userPageAction UP.layoutUser
selectSpec (AnnotationDocumentView i) = layout0 $ focus _annotationdocumentviewState _annotationdocumentviewAction D.docview selectSpec (AnnotationDocumentView i) = layout0 $ focus _annotationdocumentviewState _annotationdocumentviewAction D.docview
selectSpec Tabview = layout0 $ focus _tabviewState _tabviewAction TV.tabSpec
-- To be removed -- To be removed
selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec selectSpec SearchView = layout0 $ focus _searchState _searchAction S.searchSpec
...@@ -503,3 +521,9 @@ dispatchAction dispatcher _ (AnnotationDocumentView i) = do ...@@ -503,3 +521,9 @@ dispatchAction dispatcher _ (AnnotationDocumentView i) = do
_ <- dispatcher $ SetRoute $ AnnotationDocumentView i _ <- dispatcher $ SetRoute $ AnnotationDocumentView i
_ <- dispatcher $ AnnotationDocumentViewA $ D.NoOp _ <- dispatcher $ AnnotationDocumentViewA $ D.NoOp
pure unit pure unit
dispatchAction dispatcher _ Tabview = do
_ <- dispatcher $ SetRoute $ Tabview
_ <- dispatcher $ TabViewA $ TV.NoOp
pure unit
...@@ -23,6 +23,7 @@ data Routes ...@@ -23,6 +23,7 @@ data Routes
| SearchView | SearchView
| UserPage | UserPage
| AnnotationDocumentView Int | AnnotationDocumentView Int
| Tabview
instance showRoutes :: Show Routes where instance showRoutes :: Show Routes where
...@@ -33,6 +34,7 @@ instance showRoutes :: Show Routes where ...@@ -33,6 +34,7 @@ instance showRoutes :: Show Routes where
show SearchView = "SearchView" show SearchView = "SearchView"
show UserPage = "UserPage" show UserPage = "UserPage"
show (AnnotationDocumentView i) = "DocumentView" show (AnnotationDocumentView i) = "DocumentView"
show Tabview = "Tabview"
int :: Match Int int :: Match Int
int = floor <$> num int = floor <$> num
...@@ -41,6 +43,7 @@ int = floor <$> num ...@@ -41,6 +43,7 @@ int = floor <$> num
routing :: Match Routes routing :: Match Routes
routing = routing =
loginRoute loginRoute
<|> tabview
<|> documentView <|> documentView
<|> userPageRoute <|> userPageRoute
<|> searchRoute <|> searchRoute
...@@ -48,6 +51,7 @@ routing = ...@@ -48,6 +51,7 @@ routing =
<|> addcorpusRoute <|> addcorpusRoute
<|> home <|> home
where where
tabview = Tabview <$ route "tabview"
documentView = AnnotationDocumentView <$> (route "documentView" *> int) documentView = AnnotationDocumentView <$> (route "documentView" *> int)
userPageRoute = UserPage <$ route "userPage" userPageRoute = UserPage <$ route "userPage"
searchRoute = SearchView <$ route "search" searchRoute = SearchView <$ route "search"
......
...@@ -21,6 +21,7 @@ data Action ...@@ -21,6 +21,7 @@ data Action
| AuthorviewA AV.Action | AuthorviewA AV.Action
| TermsviewA TV.Action | TermsviewA TV.Action
| ChangeTab | ChangeTab
| NoOp
data TabTitle = TabTitle String Int data TabTitle = TabTitle String Int
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment