Commit fd66a25f authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[texts] some work on adding top bar to texts

parent 650d443f
...@@ -3,12 +3,14 @@ module Gargantext.Components.App where ...@@ -3,12 +3,14 @@ module Gargantext.Components.App where
import Data.Array (fromFoldable) import Data.Array (fromFoldable)
import Data.Maybe (Maybe(..), maybe') import Data.Maybe (Maybe(..), maybe')
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Footer (footer) import Gargantext.Components.Footer (footer)
import Gargantext.Components.Forest (forestLayout) import Gargantext.Components.Forest (forestLayout, forestLayoutWithTopBar)
import Gargantext.Components.GraphExplorer (explorerLayout) import Gargantext.Components.GraphExplorer (explorerLayout)
import Gargantext.Components.Lang (LandingLang(..)) import Gargantext.Components.Lang (LandingLang(..))
import Gargantext.Components.Login (login) import Gargantext.Components.Login (login)
...@@ -21,7 +23,7 @@ import Gargantext.Components.Nodes.File (fileLayout) ...@@ -21,7 +23,7 @@ import Gargantext.Components.Nodes.File (fileLayout)
import Gargantext.Components.Nodes.Frame (frameLayout) import Gargantext.Components.Nodes.Frame (frameLayout)
import Gargantext.Components.Nodes.Home (homeLayout) import Gargantext.Components.Nodes.Home (homeLayout)
import Gargantext.Components.Nodes.Lists (listsLayout) import Gargantext.Components.Nodes.Lists (listsLayout)
import Gargantext.Components.Nodes.Texts (textsLayout) import Gargantext.Components.Nodes.Texts as Texts
import Gargantext.Components.SimpleLayout (simpleLayout) import Gargantext.Components.SimpleLayout (simpleLayout)
import Gargantext.Config (defaultFrontends, defaultBackends, publicBackend) import Gargantext.Config (defaultFrontends, defaultBackends, publicBackend)
import Gargantext.Hooks.Router (useHashRouter) import Gargantext.Hooks.Router (useHashRouter)
...@@ -30,6 +32,7 @@ import Gargantext.Routes (AppRoute(..)) ...@@ -30,6 +32,7 @@ import Gargantext.Routes (AppRoute(..))
import Gargantext.Sessions (useSessions) import Gargantext.Sessions (useSessions)
import Gargantext.Sessions as Sessions import Gargantext.Sessions as Sessions
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.App" thisModule = "Gargantext.Components.App"
...@@ -53,7 +56,7 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -53,7 +56,7 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
showLogin <- R.useState' false showLogin <- R.useState' false
backend <- R.useState' Nothing backend <- R.useState' Nothing
reload <- R.useState' 0 appReload <- R.useState' 0
showCorpus <- R.useState' false showCorpus <- R.useState' false
...@@ -61,16 +64,26 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -61,16 +64,26 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
let backends = fromFoldable defaultBackends let backends = fromFoldable defaultBackends
let ff f session = R.fragment [ f session, footer { session } ] let ff f session = R.fragment [ f session, footer { session } ]
let forested = forestLayout { appReload: reload let forested = forestLayout { appReload
, asyncTasksRef , asyncTasksRef
, backend , backend
, frontends , frontends
, handed , handed
, route: fst route , route: fst route
, sessions: fst sessions , sessions: fst sessions
, showLogin: snd showLogin , showLogin: snd showLogin
, treeReloadRef , treeReloadRef
} }
let forestedTB = forestLayoutWithTopBar { appReload
, asyncTasksRef
, backend
, frontends
, handed
, route: fst route
, sessions: fst sessions
, showLogin: snd showLogin
, treeReloadRef
}
let defaultView _ = forested [ let defaultView _ = forested [
homeLayout { backend homeLayout { backend
, lang: LL_EN , lang: LL_EN
...@@ -94,7 +107,7 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -94,7 +107,7 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
ContactPage sid aId nodeId -> withSession sid $ \session -> forested [ ContactPage sid aId nodeId -> withSession sid $ \session -> forested [
annuaireUserLayout { annuaireUserLayout {
annuaireId: aId annuaireId: aId
, appReload: reload , appReload
, asyncTasksRef , asyncTasksRef
, frontends , frontends
, nodeId , nodeId
...@@ -123,16 +136,17 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -123,16 +136,17 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
Home -> forested [ Home -> forested [
homeLayout { backend, lang: LL_EN, publicBackend, sessions, visible: showLogin } homeLayout { backend, lang: LL_EN, publicBackend, sessions, visible: showLogin }
] ]
Lists sid nodeId -> withSession sid $ \session -> forested [ Lists sid nodeId -> withSession sid $
listsLayout { \session -> forested [
appReload: reload listsLayout {
, asyncTasksRef appReload
, nodeId , asyncTasksRef
, session , nodeId
, sessionUpdate , session
, treeReloadRef , sessionUpdate
} , treeReloadRef
] }
]
Login -> login { backend, backends, sessions, visible: showLogin } Login -> login { backend, backends, sessions, visible: showLogin }
PGraphExplorer sid graphId -> PGraphExplorer sid graphId ->
withSession sid $ withSession sid $
...@@ -162,12 +176,29 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -162,12 +176,29 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
Team sid nodeId -> withSession sid $ \session -> forested [ Team sid nodeId -> withSession sid $ \session -> forested [
corpusLayout { nodeId, session } corpusLayout { nodeId, session }
] ]
Texts sid nodeId -> withSession sid $ \session -> forested [ Texts sid nodeId -> withSession sid $
textsLayout { frontends, nodeId, session, sessionUpdate } \session -> Texts.textsWithForest {
] forestProps: {
appReload
, asyncTasksRef
, backend
, frontends
, handed
, route: fst route
, sessions: fst sessions
, showLogin: snd showLogin
, treeReloadRef
}
, textsProps: {
frontends
, nodeId
, session
, sessionUpdate
}
} []
UserPage sid nodeId -> withSession sid $ \session -> forested [ UserPage sid nodeId -> withSession sid $ \session -> forested [
userLayout { userLayout {
appReload: reload appReload
, asyncTasksRef , asyncTasksRef
, frontends , frontends
, nodeId , nodeId
......
module Gargantext.Components.Forest where module Gargantext.Components.Forest where
import Data.Array (reverse) import Data.Array as A
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), fromMaybe)
import Data.Set as Set import Data.Set as Set
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -133,7 +133,20 @@ forestLayoutCpt :: R.Component ForestLayoutProps ...@@ -133,7 +133,20 @@ forestLayoutCpt :: R.Component ForestLayoutProps
forestLayoutCpt = R.hooksComponentWithModule thisModule "forestLayout" cpt forestLayoutCpt = R.hooksComponentWithModule thisModule "forestLayout" cpt
where where
cpt props@{ handed } children = do cpt props@{ handed } children = do
pure $ R.fragment [ topBar { handed }, forestLayoutMain props children ] pure $ R.fragment [ topBar { handed } [], forestLayoutMain props children ]
-- a component, for which first child element is placed inside the top bar
-- while the remaining ones are put into the main view
forestLayoutWithTopBar :: R2.Component ForestLayoutProps
forestLayoutWithTopBar props = R.createElement forestLayoutWithTopBarCpt props
forestLayoutWithTopBarCpt :: R.Component ForestLayoutProps
forestLayoutWithTopBarCpt = R.hooksComponentWithModule thisModule "forestLayoutWithTopBar" cpt
where
cpt props@{ handed } children = do
let { head: topBarChild, tail: mainChildren } =
fromMaybe { head: H.div {} [], tail: [] } $ A.uncons children
pure $ R.fragment [ topBar { handed } [ topBarChild ], forestLayoutMain props mainChildren ]
forestLayoutMain :: R2.Component ForestLayoutProps forestLayoutMain :: R2.Component ForestLayoutProps
forestLayoutMain props = R.createElement forestLayoutMainCpt props forestLayoutMain props = R.createElement forestLayoutMainCpt props
...@@ -152,22 +165,22 @@ forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" c ...@@ -152,22 +165,22 @@ forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" c
, treeReloadRef } children = do , treeReloadRef } children = do
let ordering = let ordering =
case fst handed of case fst handed of
LeftHanded -> reverse LeftHanded -> A.reverse
RightHanded -> identity RightHanded -> identity
pure $ R2.row $ ordering [ pure $ R2.row $ ordering [
H.div { className: "col-md-2", style: { paddingTop: "60px" } } H.div { className: "col-md-2", style: { paddingTop: "60px" } } [
[ forest { appReload forest { appReload
, asyncTasksRef , asyncTasksRef
, backend , backend
, frontends , frontends
, handed: fst handed , handed: fst handed
, route , route
, sessions , sessions
, showLogin , showLogin
, treeReloadRef } ] , treeReloadRef } ]
, mainPage {} children , mainPage {} children
] ]
mainPage :: R2.Component () mainPage :: R2.Component ()
mainPage = R.createElement mainPageCpt mainPage = R.createElement mainPageCpt
......
...@@ -38,11 +38,12 @@ import Gargantext.Types (ID, Reload, isPublic, publicize) ...@@ -38,11 +38,12 @@ import Gargantext.Types (ID, Reload, isPublic, publicize)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree" thisModule = "Gargantext.Components.Forest.Tree"
------------------------------------------------------------------------ ------------------------------------------------------------------------
type CommonProps = type CommonProps = (
( frontends :: Frontends frontends :: Frontends
, handed :: GT.Handed , handed :: GT.Handed
, mCurrentRoute :: Maybe AppRoute , mCurrentRoute :: Maybe AppRoute
, openNodes :: R.State OpenNodes , openNodes :: R.State OpenNodes
...@@ -51,10 +52,11 @@ type CommonProps = ...@@ -51,10 +52,11 @@ type CommonProps =
) )
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Props = ( asyncTasks :: GAT.Reductor type Props = (
, root :: ID asyncTasks :: GAT.Reductor
| CommonProps , root :: ID
) | CommonProps
)
treeView :: Record Props -> R.Element treeView :: Record Props -> R.Element
treeView props = R.createElement treeViewCpt props [] treeView props = R.createElement treeViewCpt props []
...@@ -70,16 +72,16 @@ treeView props = R.createElement treeViewCpt props [] ...@@ -70,16 +72,16 @@ treeView props = R.createElement treeViewCpt props []
, reload , reload
, root , root
, session , session
} _children = pure } _children = do
$ treeLoadView { asyncTasks pure $ treeLoadView { asyncTasks
, frontends , frontends
, handed , handed
, mCurrentRoute , mCurrentRoute
, openNodes , openNodes
, reload , reload
, root , root
, session , session
} }
treeLoadView :: Record Props -> R.Element treeLoadView :: Record Props -> R.Element
treeLoadView p = R.createElement treeLoadViewCpt p [] treeLoadView p = R.createElement treeLoadViewCpt p []
...@@ -114,10 +116,11 @@ getNodeTree :: Session -> GT.ID -> Aff FTree ...@@ -114,10 +116,11 @@ getNodeTree :: Session -> GT.ID -> Aff FTree
getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) "" getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
-------------- --------------
type TreeViewProps = ( asyncTasks :: GAT.Reductor type TreeViewProps = (
, tree :: FTree asyncTasks :: GAT.Reductor
| CommonProps , tree :: FTree
) | CommonProps
)
loadedTreeView :: Record TreeViewProps -> R.Element loadedTreeView :: Record TreeViewProps -> R.Element
loadedTreeView p = R.createElement loadedTreeViewCpt p [] loadedTreeView p = R.createElement loadedTreeViewCpt p []
...@@ -134,30 +137,27 @@ loadedTreeView p = R.createElement loadedTreeViewCpt p [] ...@@ -134,30 +137,27 @@ loadedTreeView p = R.createElement loadedTreeViewCpt p []
, session , session
-- , tasks -- , tasks
, tree , tree
} _ = pure $ H.ul { className: "tree" } _ = do
} pure $ H.ul { className: "tree" } [
[ H.div { className: if handed == GT.RightHanded H.div { className: if handed == GT.RightHanded then "righthanded" else "lefthanded" } [
then "righthanded" toHtml { asyncTasks
else "lefthanded" , frontends
} , handed
[ toHtml { asyncTasks , mCurrentRoute
, frontends , openNodes
, handed , reload
, mCurrentRoute , session
, openNodes -- , tasks
, reload , tree
, session }
-- , tasks ]
, tree ]
}
]
]
------------------------------------------------------------------------ ------------------------------------------------------------------------
type ToHtmlProps = type ToHtmlProps = (
( asyncTasks :: GAT.Reductor asyncTasks :: GAT.Reductor
-- , tasks :: Record Tasks -- , tasks :: Record Tasks
, tree :: FTree , tree :: FTree
| CommonProps | CommonProps
......
...@@ -17,7 +17,7 @@ controlsToggleButton :: Record Props -> R.Element ...@@ -17,7 +17,7 @@ controlsToggleButton :: Record Props -> R.Element
controlsToggleButton props = R.createElement controlsToggleButtonCpt props [] controlsToggleButton props = R.createElement controlsToggleButtonCpt props []
controlsToggleButtonCpt :: R.Component Props controlsToggleButtonCpt :: R.Component Props
controlsToggleButtonCpt = R.hooksComponentWithModule thisModule "graphControlsToggleButton" cpt controlsToggleButtonCpt = R.hooksComponentWithModule thisModule "controlsToggleButton" cpt
where where
cpt {state} _ = do cpt {state} _ = do
let (open /\ setOpen) = state let (open /\ setOpen) = state
......
...@@ -24,7 +24,6 @@ import Gargantext.Utils.Reactix as R2 ...@@ -24,7 +24,6 @@ import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.Nodes.Lists" thisModule = "Gargantext.Components.Nodes.Lists"
------------------------------------------------------------------------ ------------------------------------------------------------------------
------------------------------------------------------------------------
type Props = ( type Props = (
appReload :: GT.ReloadS appReload :: GT.ReloadS
......
...@@ -10,9 +10,11 @@ import Effect (Effect) ...@@ -10,9 +10,11 @@ import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Record as Record
-------------------------------------------------------- --------------------------------------------------------
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Forest as Forest
import Gargantext.Components.Loader (loader) import Gargantext.Components.Loader (loader)
import Gargantext.Components.NgramsTable.Loader (clearCache) import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
...@@ -20,50 +22,112 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) ...@@ -20,50 +22,112 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo) import Gargantext.Components.Nodes.Corpus.Chart.Histo (histo)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, Hyperdata(..), getCorpusInfo, CorpusInfo(..)) import Gargantext.Components.Nodes.Corpus.Types (CorpusData, Hyperdata(..), getCorpusInfo, CorpusInfo(..))
import Gargantext.Components.Nodes.Lists.Types as NT import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Nodes.Texts.SidePanelToggleButton (sidePanelToggleButton)
import Gargantext.Components.Nodes.Texts.Types
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session, Sessions, sessionId, getCacheState, setCacheState) import Gargantext.Sessions (Session, Sessions, sessionId, getCacheState, setCacheState)
import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..)) import Gargantext.Types (CTabNgramType(..), Handed(..), ReloadS, TabSubType(..), TabType(..))
import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.Nodes.Texts" thisModule = "Gargantext.Components.Nodes.Texts"
-------------------------------------------------------- --------------------------------------------------------
type TextsWithForest = (
forestProps :: Record Forest.ForestLayoutProps
, textsProps :: Record CommonProps
)
type Props = ( textsWithForest :: R2.Component TextsWithForest
frontends :: Frontends textsWithForest = R.createElement textsWithForestCpt
, nodeId :: Int
, session :: Session textsWithForestCpt :: R.Component TextsWithForest
, sessionUpdate :: Session -> Effect Unit textsWithForestCpt = R.hooksComponentWithModule thisModule "textsWithForest" cpt
where
cpt { forestProps
, textsProps } _ = do
controls <- initialControls
pure $ Forest.forestLayoutWithTopBar forestProps [
topBar { controls } []
, textsLayout (Record.merge textsProps { controls }) []
]
--------------------------------------------------------
type TextsLayoutControls = (
showSidePanel :: R.State SidePanelState
)
initialControls :: R.Hooks (Record TextsLayoutControls)
initialControls = do
showSidePanel <- R.useState' InitialClosed
pure $ {
showSidePanel
}
type TopBarProps = (
controls :: Record TextsLayoutControls
) )
textsLayout :: Record Props -> R.Element topBar :: R2.Component TopBarProps
textsLayout props = R.createElement textsLayoutCpt props [] topBar = R.createElement topBarCpt
topBarCpt :: R.Component TopBarProps
topBarCpt = R.hooksComponentWithModule thisModule "topBar" cpt
where
cpt { controls } _ = do
pure $
H.ul { className: "nav navbar-nav" } [
H.li {} [
sidePanelToggleButton { state: controls.showSidePanel } []
]
] -- head (goes to top bar)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type CommonProps = (
frontends :: Frontends
, nodeId :: Int
, session :: Session
, sessionUpdate :: Session -> Effect Unit
)
type Props = (
controls :: Record TextsLayoutControls
| CommonProps
)
textsLayout :: R2.Component Props
textsLayout = R.createElement textsLayoutCpt
textsLayoutCpt :: R.Component Props textsLayoutCpt :: R.Component Props
textsLayoutCpt = R.hooksComponentWithModule thisModule "textsLayout" cpt where textsLayoutCpt = R.hooksComponentWithModule thisModule "textsLayout" cpt
cpt { frontends, nodeId, session, sessionUpdate } _ = do where
let sid = sessionId session cpt { controls, frontends, nodeId, session, sessionUpdate } children = do
let sid = sessionId session
pure $ textsLayoutWithKey { frontends pure $ textsLayoutWithKey { controls
, key: show sid <> "-" <> show nodeId , frontends
, nodeId , key: show sid <> "-" <> show nodeId
, session , nodeId
, sessionUpdate } , session
, sessionUpdate } children
type KeyProps = ( type KeyProps = (
key :: String key :: String
| Props | Props
) )
textsLayoutWithKey :: Record KeyProps -> R.Element textsLayoutWithKey :: R2.Component KeyProps
textsLayoutWithKey props = R.createElement textsLayoutWithKeyCpt props [] textsLayoutWithKey = R.createElement textsLayoutWithKeyCpt
textsLayoutWithKeyCpt :: R.Component KeyProps textsLayoutWithKeyCpt :: R.Component KeyProps
textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKey" cpt textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKey" cpt
where where
cpt { frontends, nodeId, session, sessionUpdate } _ = do cpt { frontends, nodeId, session, sessionUpdate } _children = do
cacheState <- R.useState' $ getCacheState NT.CacheOff session nodeId cacheState <- R.useState' $ getCacheState NT.CacheOff session nodeId
pure $ loader { nodeId, session } loadCorpusWithChild $ pure $ loader { nodeId, session } loadCorpusWithChild $
......
module Gargantext.Components.Nodes.Texts.SidePanelToggleButton
( Props, sidePanelToggleButton
) where
import Data.Tuple.Nested ((/\))
import Prelude
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Nodes.Texts.Types
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Nodes.Texts.SidePanelToggleButton"
type Props = ( state :: R.State SidePanelState )
sidePanelToggleButton :: R2.Component Props
sidePanelToggleButton = R.createElement sidePanelToggleButtonCpt
sidePanelToggleButtonCpt :: R.Component Props
sidePanelToggleButtonCpt = R.hooksComponentWithModule thisModule "sidePanelToggleButton" cpt
where
cpt { state } _ = do
let (open /\ setOpen) = state
pure $
H.button { className: "btn btn-primary"
, on: { click: \_ -> setOpen $ toggleSidePanelState } } [ H.text (text open) ]
text InitialClosed = "Show Side Panel"
text Opened = "Show Side Panel"
text Closed = "Hide Side Panel"
module Gargantext.Components.Nodes.Texts.Types where
import Gargantext.Prelude
data SidePanelState = InitialClosed | Opened | Closed
derive instance eqSidePanelState :: Eq SidePanelState
toggleSidePanelState :: SidePanelState -> SidePanelState
toggleSidePanelState InitialClosed = Opened
toggleSidePanelState Closed = Opened
toggleSidePanelState Opened = Closed
...@@ -26,5 +26,5 @@ simpleLayoutCpt = R.hooksComponentWithModule thisModule "simpleLayout" cpt ...@@ -26,5 +26,5 @@ simpleLayoutCpt = R.hooksComponentWithModule thisModule "simpleLayout" cpt
where where
cpt { handed } children = do cpt { handed } children = do
pure $ H.div { className: "simple-layout" } ( pure $ H.div { className: "simple-layout" } (
[ topBar { handed } ] <> children <> [ license ] [ topBar { handed } [] ] <> children <> [ license ]
) )
...@@ -10,6 +10,7 @@ import Reactix.DOM.HTML as H ...@@ -10,6 +10,7 @@ import Reactix.DOM.HTML as H
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types (Handed(..)) import Gargantext.Types (Handed(..))
import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.TopBar" thisModule = "Gargantext.Components.TopBar"
...@@ -18,42 +19,42 @@ type TopBarProps = ( ...@@ -18,42 +19,42 @@ type TopBarProps = (
handed :: R.State Handed handed :: R.State Handed
) )
topBar :: Record TopBarProps -> R.Element topBar :: R2.Component TopBarProps
topBar props = R.createElement topBarCpt props [] topBar = R.createElement topBarCpt
topBarCpt :: R.Component TopBarProps topBarCpt :: R.Component TopBarProps
topBarCpt = R.hooksComponentWithModule thisModule "topBar" cpt topBarCpt = R.hooksComponentWithModule thisModule "topBar" cpt
where where
cpt { handed } _ = do cpt { handed } children = do
pure $ H.div { id: "dafixedtop" pure $ H.div { id: "dafixedtop"
, role: "navigation" , role: "navigation"
, className: "navbar navbar-inverse navbar-fixed-top" } , className: "navbar navbar-inverse navbar-fixed-top" }
[ H.div { className: "container-fluid" } [ H.div { className: "container-fluid" }
[ H.div { className: "navbar-inner" } [ H.div { className: "navbar-inner" }
[ logo (fst handed) [ logo (fst handed)
, H.div { className: "collapse navbar-collapse" <> navHanded} , H.div { className: "collapse navbar-collapse" <> navHanded} (
$ sortHanded [
[ H.ul { className: "nav navbar-nav" <> navHanded} [divDropdownLeft] H.ul { className: "nav navbar-nav" <> navHanded} []
, H.ul { title: "If you are Left Handed you can change " , H.ul { title: "If you are Left Handed you can change "
<> "the interface by clicking on me. Click " <> "the interface by clicking on me. Click "
<> "again to come back to previous state." <> "again to come back to previous state."
, className: "nav navbar-nav" <> navHanded , className: "nav navbar-nav" <> navHanded
} [handedChooser { handed }] } [handedChooser { handed }]
, H.ul { className: "nav navbar-nav" <> navHanded} [] , H.ul { className: "nav navbar-nav" <> navHanded} [divDropdownLeft]
{-, H.ul { title: "Dark Mode soon here" {-, H.ul { title: "Dark Mode soon here"
, className : "nav navbar-nav" , className : "nav navbar-nav"
} [ H.li {} [ H.a {} [ H.span {className : "fa fa-moon"}[] } [ H.li {} [ H.a {} [ H.span {className : "fa fa-moon"}[]
] ]
] ]
] ]
-} -}
] ] <> children)
] ]
] ]
] ]
where where
navHanded = if fst handed == LeftHanded then " navbar-right" else "" navHanded = if fst handed == LeftHanded then " navbar-right" else ""
sortHanded = if fst handed == LeftHanded then reverse else reverse -- identity -- sortHanded = if fst handed == LeftHanded then reverse else reverse -- identity
-- SB.searchBar {session, databases: allDatabases} -- SB.searchBar {session, databases: allDatabases}
......
...@@ -117,7 +117,9 @@ instance encodeJsonSessions :: EncodeJson Sessions where ...@@ -117,7 +117,9 @@ instance encodeJsonSessions :: EncodeJson Sessions where
unSessions :: Sessions -> Array Session unSessions :: Sessions -> Array Session
unSessions (Sessions {sessions:s}) = A.fromFoldable s unSessions (Sessions {sessions:s}) = A.fromFoldable s
useSessions :: R.Hooks (R2.Reductor Sessions Action) type Reductor = R2.Reductor Sessions Action
useSessions :: R.Hooks Reductor
useSessions = R2.useReductor actAndSave (const loadSessions) unit useSessions = R2.useReductor actAndSave (const loadSessions) unit
where where
actAndSave :: R2.Actor Sessions Action actAndSave :: R2.Actor Sessions Action
......
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