Commit 20a7cbb9 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[forest] more work on graph explorer, tree hiding works

But controls doesn't and sidebar throws exception...
parent 12910a76
......@@ -16,59 +16,59 @@ import Gargantext.Types (Handed(RightHanded), SidePanelState(..))
import Gargantext.Utils.Toestand as T2
type App =
{ backend :: Maybe Backend
, forestOpen :: OpenNodes
, graphVersion :: T2.Reload
, handed :: Handed
, reloadForest :: Int
, reloadRoot :: Int
, route :: AppRoute
, sessions :: Sessions
, showCorpus :: Boolean
, showLogin :: Boolean
, showTree :: Boolean
, sidePanelGraph :: Maybe (Record GEST.SidePanel)
, sidePanelLists :: Maybe (Record ListsT.SidePanel)
, sidePanelTexts :: Maybe (Record TextsT.SidePanel)
, sidePanelState :: SidePanelState
, tasks :: GAT.Storage
{ backend :: Maybe Backend
, forestOpen :: OpenNodes
, graphVersion :: T2.Reload
, handed :: Handed
, reloadForest :: Int
, reloadRoot :: Int
, route :: AppRoute
, sessions :: Sessions
, showCorpus :: Boolean
, showLogin :: Boolean
, showTree :: Boolean
, sidePanelGraph :: Maybe (Record GEST.SidePanel)
, sidePanelLists :: Maybe (Record ListsT.SidePanel)
, sidePanelTexts :: Maybe (Record TextsT.SidePanel)
, sidePanelState :: SidePanelState
, tasks :: GAT.Storage
}
emptyApp :: App
emptyApp =
{ backend : Nothing
, forestOpen : Set.empty
, graphVersion : T2.newReload
, handed : RightHanded
, reloadForest : T2.newReload
, reloadRoot : T2.newReload
, route : Home
, sessions : Sessions.empty
, showCorpus : false
, showLogin : false
, showTree : true
, sidePanelGraph : GEST.initialSidePanel
, sidePanelLists : ListsT.initialSidePanel
, sidePanelTexts : TextsT.initialSidePanel
, sidePanelState : InitialClosed
, tasks : GAT.empty
{ backend : Nothing
, forestOpen : Set.empty
, graphVersion : T2.newReload
, handed : RightHanded
, reloadForest : T2.newReload
, reloadRoot : T2.newReload
, route : Home
, sessions : Sessions.empty
, showCorpus : false
, showLogin : false
, showTree : true
, sidePanelGraph : GEST.initialSidePanel
, sidePanelLists : ListsT.initialSidePanel
, sidePanelTexts : TextsT.initialSidePanel
, sidePanelState : InitialClosed
, tasks : GAT.empty
}
type Boxes =
{ backend :: T.Box (Maybe Backend)
, forestOpen :: T.Box OpenNodes
, graphVersion :: T2.ReloadS
, handed :: T.Box Handed
, reloadForest :: T.Box T2.Reload
, reloadRoot :: T.Box T2.Reload
, route :: T.Box AppRoute
, sessions :: T.Box Sessions
, showCorpus :: T.Box Boolean
, showLogin :: T.Box Boolean
, showTree :: T.Box Boolean
, sidePanelGraph :: T.Box (Maybe (Record GEST.SidePanel))
, sidePanelLists :: T.Box (Maybe (Record ListsT.SidePanel))
, sidePanelTexts :: T.Box (Maybe (Record TextsT.SidePanel))
, sidePanelState :: T.Box SidePanelState
, tasks :: T.Box GAT.Storage
{ backend :: T.Box (Maybe Backend)
, forestOpen :: T.Box OpenNodes
, graphVersion :: T2.ReloadS
, handed :: T.Box Handed
, reloadForest :: T.Box T2.Reload
, reloadRoot :: T.Box T2.Reload
, route :: T.Box AppRoute
, sessions :: T.Box Sessions
, showCorpus :: T.Box Boolean
, showLogin :: T.Box Boolean
, showTree :: T.Box Boolean
, sidePanelGraph :: T.Box (Maybe (Record GEST.SidePanel))
, sidePanelLists :: T.Box (Maybe (Record ListsT.SidePanel))
, sidePanelTexts :: T.Box (Maybe (Record TextsT.SidePanel))
, sidePanelState :: T.Box SidePanelState
, tasks :: T.Box GAT.Storage
}
......@@ -10,7 +10,6 @@ module Gargantext.Components.Forest
import Data.Array as A
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -45,6 +44,7 @@ type Props =
, reloadForest :: T.Box T2.Reload
, sessions :: T.Box Sessions
, showLogin :: T.Box Boolean
, showTree :: T.Box Boolean
, tasks :: T.Box GAT.Storage
| Common
)
......@@ -68,6 +68,7 @@ forestCpt = here.component "forest" cpt where
, route
, sessions
, showLogin
, showTree
, tasks } _ = do
-- TODO Fix this. I think tasks shouldn't be a Box but only a Reductor
-- tasks' <- GAT.useTasks reloadRoot reloadForest
......@@ -80,17 +81,21 @@ forestCpt = here.component "forest" cpt where
forestOpen' <- T.useLive T.unequal forestOpen
sessions' <- T.useLive T.unequal sessions
showTree' <- T.useLive T.unequal showTree
-- TODO If `reloadForest` is set, `reload` state should be updated
-- TODO fix tasks ref
-- R.useEffect' $ do
-- R.setRef tasks $ Just tasks'
R2.useCache
( frontends /\ sessions' /\ handed' /\ forestOpen' /\ reloadForest' )
(cp handed' sessions')
( forestOpen' /\ frontends /\ handed' /\ reloadForest' /\ sessions' /\ showTree' )
(cp handed' sessions' showTree')
where
common = RX.pick props :: Record Common
cp handed' sessions' _ =
pure $ H.div { className: "forest" }
cp handed' sessions' showTree' _ = do
let className = "forest " <> if showTree' then "" else "d-none"
pure $ H.div { className }
(A.cons (plus handed' showLogin) (trees handed' sessions'))
trees handed' sessions' = (tree handed') <$> unSessions sessions'
tree handed' s@(Session {treeId}) =
......@@ -169,6 +174,7 @@ forestLayoutRawCpt = here.component "forestLayoutRaw" cpt where
, reloadRoot
, route
, sessions
, showTree
, showLogin
, tasks } children = do
handed' <- T.useLive T.unequal p.handed
......@@ -187,6 +193,7 @@ forestLayoutRawCpt = here.component "forestLayoutRaw" cpt where
, reloadRoot
, route
, sessions
, showTree
, showLogin
, tasks } []
......
......@@ -14,6 +14,14 @@ import Data.Set as Set
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Math (log)
import Partial.Unsafe (unsafePartial)
import Reactix as R
import Reactix.DOM.HTML as RH
import Record as Record
import Record.Extra as RX
import Toestand as T
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Forest (forest)
......@@ -35,13 +43,6 @@ import Gargantext.Types as Types
import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Math (log)
import Partial.Unsafe (unsafePartial)
import Reactix as R
import Reactix.DOM.HTML as RH
import Record as Record
import Record.Extra as RX
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.GraphExplorer"
......@@ -108,7 +109,7 @@ explorerCpt :: R.Component Props
explorerCpt = here.component "explorer" cpt
where
cpt props@{ backend
, boxes: boxes@{ graphVersion, sidePanelGraph }
, boxes: boxes@{ graphVersion, showTree, sidePanelGraph }
, frontends
, graph
, graphId
......@@ -141,21 +142,22 @@ explorerCpt = here.component "explorer" cpt
, graph
, graphId
, hyperdataGraph
, reloadForest: \_ -> T2.reload reloadForest
, reloadForest
, session
, showTree
, sidePanel: sidePanelGraph
, sidePanelState
}
multiSelectEnabled' <- T.useLive T.unequal controls.multiSelectEnabled
showTree' <- T.useLive T.unequal controls.showTree
multiSelectEnabledRef <- R.useRef multiSelectEnabled'
sidePanel@{ mGraph, mMetaData, sideTab } <- GEST.focusedSidePanel sidePanelGraph
{ mGraph, mMetaData, sideTab } <- GEST.focusedSidePanel sidePanelGraph
R.useEffectOnce' $ do
T.write_ (Just graph) mGraph
T.write_ mMetaData' mMetaData
forestOpen <- T.useBox $ Set.empty
forestOpen <- T.useBox $ (Set.empty :: OpenNodes)
R.useEffectOnce' $ do
R2.loadLocalStorageState R2.openNodesKey forestOpen
T.listen (R2.listenLocalStorageState R2.openNodesKey) forestOpen
......@@ -180,30 +182,13 @@ explorerCpt = here.component "explorer" cpt
T.write_ Types.InitialClosed controls.sidePanelState
pure $
RH.div { className: "graph-meta-container" } [
-- RH.div { className: "fixed-top navbar navbar-expand-lg"
-- , id: "graph-explorer" }
-- [ topBar { controls, graph } [] ]
RH.div { className: "graph-container" } [
inner handed' [
rowControls [ Controls.controls controls ]
, RH.div { className: "row graph-row" } $ mainLayout handed' $
tree { backend
, forestOpen
, frontends
, handed
, reload: reloadForest
, route
, reloadForest
, sessions
, show: showTree'
, showLogin: showLogin
, tasks
}
/\
RH.div { ref: graphRef, id: "graph-view", className: "col-md-12" } []
/\
graphView { controls
RH.div { className: "graph-meta-container" }
[ RH.div { className: "graph-container" }
[ inner handed'
[ RH.div { id: "controls-container" } [ Controls.controls controls [] ]
, RH.div { className: "row graph-row" }
[ RH.div { ref: graphRef, id: "graph-view", className: "col-md-12" } []
, graphView { controls
, elRef: graphRef
, graphId
, graph
......@@ -211,72 +196,16 @@ explorerCpt = here.component "explorer" cpt
, mMetaData
, multiSelectEnabledRef
} []
/\
mSidebar (Record.merge sidePanel { frontends
, graph
, graphId
, graphVersion
, reloadForest
, removedNodeIds : controls.removedNodeIds
, session
, sideTab
}) []
]
]
]
]
mainLayout Types.RightHanded (tree' /\ gc /\ gv /\ sdb) = [tree', gc, gv, sdb]
mainLayout Types.LeftHanded (tree' /\ gc /\ gv /\ sdb) = [sdb, gc, gv, tree']
outer = RH.div { className: "col-md-12" }
inner h = RH.div { className: "container-fluid " <> hClass }
where
hClass = case h of
Types.LeftHanded -> "lefthanded"
Types.RightHanded -> "righthanded"
rowControls = RH.div { id: "controls-container" }
pullLeft = RH.div { className: "pull-left" }
pullRight = RH.div { className: "pull-right" }
tree :: Record TreeProps -> R.Element
tree { show: false } = RH.div { id: "tree" } []
tree { backend, forestOpen, frontends, handed, reload, route, sessions, showLogin, reloadForest, tasks } =
RH.div {className: "col-md-2 graph-tree"} [
forest { backend
, forestOpen
, frontends
, handed
, reloadForest
, reloadRoot: reload
, route
, sessions
, showLogin
, tasks } []
]
type MSideBar =
(
mGraph :: T.Box (Maybe SigmaxT.SGraph)
, mMetaData :: T.Box (Maybe GET.MetaData)
, multiSelectEnabled :: T.Box Boolean
-- , selectedNodeIds :: T.Box SigmaxT.NodeIds
, showControls :: T.Box Boolean
| MSidebarProps
)
mSidebar :: R2.Component MSideBar
mSidebar = R.createElement mSidebarCpt
mSidebarCpt :: R.Component MSideBar
mSidebarCpt = here.component "mSidebar" cpt where
cpt props@{ mMetaData } _ = do
mMetaData' <- T.useLive T.unequal mMetaData
case mMetaData' of
Nothing -> pure $ RH.div {} []
Just metaData -> do
pure $ Sidebar.sidebar (Record.merge (RX.pick props :: Record MSidebarProps) { metaData }) []
type TopBar =
(
......@@ -316,32 +245,6 @@ topBarCpt = here.component "topBar" cpt where
-- spaces = RH.div { className: "flex-space-between" }
spaces = RH.a { className: "nav-link" }
type TreeProps = (
backend :: T.Box (Maybe Backend)
, forestOpen :: T.Box OpenNodes
, frontends :: Frontends
, handed :: T.Box Types.Handed
, reload :: T.Box T2.Reload
, reloadForest :: T.Box T2.Reload
, route :: T.Box AppRoute
, sessions :: T.Box Sessions
, show :: Boolean
, showLogin :: T.Box Boolean
, tasks :: T.Box GAT.Storage
)
type MSidebarProps =
( frontends :: Frontends
, graph :: SigmaxT.SGraph
, graphId :: GET.GraphId
, graphVersion :: T2.ReloadS
, reloadForest :: T.Box T2.Reload
, removedNodeIds :: T.Box SigmaxT.NodeIds
, selectedNodeIds :: T.Box SigmaxT.NodeIds
, session :: Session
, sideTab :: T.Box GET.SideTab
)
type GraphProps = (
controls :: Record Controls.Controls
, elRef :: R.Ref (Nullable Element)
......
......@@ -23,6 +23,7 @@ import Gargantext.Hooks.Sigmax as Sigmax
import Gargantext.Hooks.Sigmax.Sigma as Sigma
import Gargantext.Sessions (Session)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.GraphExplorer.Button"
......@@ -53,12 +54,12 @@ centerButton sigmaRef = simpleButton {
}
type CameraButtonProps = (
id :: Int
type CameraButtonProps =
( id :: Int
, hyperdataGraph :: GET.HyperdataGraph
, session :: Session
, sigmaRef :: R.Ref Sigmax.Sigma
, reloadForest :: Unit -> Effect Unit
, session :: Session
, sigmaRef :: R.Ref Sigmax.Sigma
, reloadForest :: T2.ReloadS
)
......@@ -94,7 +95,7 @@ cameraButton { id
launchAff_ $ do
clonedGraphId <- cloneGraph { id, hyperdataGraph: hyperdataGraph', session }
ret <- uploadArbitraryDataURL session clonedGraphId (Just $ nowStr <> "-" <> "screenshot.png") screen
liftEffect $ reloadForest unit
liftEffect $ T2.reload reloadForest
pure ret
, text: "Screenshot"
}
......@@ -3,8 +3,6 @@ module Gargantext.Components.GraphExplorer.Controls
, useGraphControls
, controls
, controlsCpt
, setShowTree
, setShowControls
) where
import Data.Array as A
......@@ -32,6 +30,7 @@ import Gargantext.Sessions (Session)
import Gargantext.Types as GT
import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.GraphExplorer.Controls"
......@@ -46,7 +45,7 @@ type Controls =
, hyperdataGraph :: GET.HyperdataGraph
, multiSelectEnabled :: T.Box Boolean
, nodeSize :: T.Box Range.NumberRange
, reloadForest :: Unit -> Effect Unit
, reloadForest :: T2.ReloadS
, removedNodeIds :: T.Box SigmaxT.NodeIds
, selectedNodeIds :: T.Box SigmaxT.NodeIds
, session :: Session
......@@ -66,8 +65,8 @@ initialLocalControls = do
mouseSelectorSize <- T.useBox 15.0
pure $ { labelSize, mouseSelectorSize }
controls :: Record Controls -> R.Element
controls props = R.createElement controlsCpt props []
controls :: R2.Component Controls
controls = R.createElement controlsCpt
controlsCpt :: R.Component Controls
controlsCpt = here.component "controls" cpt
......@@ -96,6 +95,9 @@ controlsCpt = here.component "controls" cpt
showControls' <- T.useLive T.unequal showControls
sidePanelState' <- T.useLive T.unequal sidePanelState
R.useEffect' $ do
here.log2 "showControls" showControls'
localControls <- initialLocalControls
-- ref to track automatic FA pausing
-- If user pauses FA before auto is triggered, clear the timeoutId
......@@ -160,36 +162,37 @@ controlsCpt = here.component "controls" cpt
false -> RH.div {} []
-- true -> R2.menu { id: "toolbar" } [
true -> RH.nav { className: "navbar navbar-expand-lg" }
[ RH.ul { className: "navbar-nav mx-auto" } [ -- change type button (?)
RH.li { className: "nav-item" } [ centerButton sigmaRef ]
, RH.li { className: "nav-item" } [ pauseForceAtlasButton { state: forceAtlasState } [] ]
, RH.li { className: "nav-item" } [ edgesToggleButton { state: showEdges } [] ]
, RH.li { className: "nav-item" } [ louvainToggleButton { state: showLouvain } [] ]
, RH.li { className: "nav-item" } [ edgeConfluenceControl { range: edgeConfluenceRange
, state: edgeConfluence } [] ]
, RH.li { className: "nav-item" } [ edgeWeightControl { range: edgeWeightRange
, state: edgeWeight } [] ]
-- change level
-- file upload
-- run demo
-- search button
-- search topics
, RH.li { className: "nav-item" } [ labelSizeButton sigmaRef localControls.labelSize ] -- labels size: 1-4
, RH.li { className: "nav-item" } [ nodeSizeControl { range: nodeSizeRange
, state: nodeSize } [] ]
-- zoom: 0 -100 - calculate ratio
, RH.li { className: "nav-item" } [ multiSelectEnabledButton { state: multiSelectEnabled } [] ] -- toggle multi node selection
-- save button
, RH.li { className: "nav-item" }
[ mouseSelectorSizeButton sigmaRef localControls.mouseSelectorSize ]
, RH.li { className: "nav-item" }
[ cameraButton { id: graphId
, hyperdataGraph: hyperdataGraph
, session: session
, sigmaRef: sigmaRef
, reloadForest: reloadForest } ]
]
]
[ RH.ul { className: "navbar-nav mx-auto" }
[ -- change type button (?)
navItem [ centerButton sigmaRef ]
, navItem [ pauseForceAtlasButton { state: forceAtlasState } [] ]
, navItem [ edgesToggleButton { state: showEdges } [] ]
, navItem [ louvainToggleButton { state: showLouvain } [] ]
, navItem [ edgeConfluenceControl { range: edgeConfluenceRange
, state: edgeConfluence } [] ]
, navItem [ edgeWeightControl { range: edgeWeightRange
, state: edgeWeight } [] ]
-- change level
-- file upload
-- run demo
-- search button
-- search topics
, navItem [ labelSizeButton sigmaRef localControls.labelSize ] -- labels size: 1-4
, navItem [ nodeSizeControl { range: nodeSizeRange
, state: nodeSize } [] ]
-- zoom: 0 -100 - calculate ratio
, navItem [ multiSelectEnabledButton { state: multiSelectEnabled } [] ] -- toggle multi node selection
-- save button
, navItem [ mouseSelectorSizeButton sigmaRef localControls.mouseSelectorSize ]
, navItem [ cameraButton { id: graphId
, hyperdataGraph: hyperdataGraph
, session: session
, sigmaRef: sigmaRef
, reloadForest } ]
]
]
where
navItem = RH.li { className: "nav-item" }
-- RH.ul {} [ -- change type button (?)
-- RH.li {} [ centerButton sigmaRef ]
-- , RH.li {} [ pauseForceAtlasButton {state: forceAtlasState} ]
......@@ -220,13 +223,14 @@ controlsCpt = here.component "controls" cpt
-- ]
useGraphControls :: { forceAtlasS :: SigmaxT.ForceAtlasState
, graph :: SigmaxT.SGraph
, graphId :: GET.GraphId
, hyperdataGraph :: GET.HyperdataGraph
, reloadForest :: Unit -> Effect Unit
, session :: Session
, sidePanel :: T.Box (Maybe (Record GEST.SidePanel))
, sidePanelState :: T.Box GT.SidePanelState }
, graph :: SigmaxT.SGraph
, graphId :: GET.GraphId
, hyperdataGraph :: GET.HyperdataGraph
, reloadForest :: T2.ReloadS
, session :: Session
, showTree :: T.Box Boolean
, sidePanel :: T.Box (Maybe (Record GEST.SidePanel))
, sidePanelState :: T.Box GT.SidePanelState }
-> R.Hooks (Record Controls)
useGraphControls { forceAtlasS
, graph
......@@ -234,6 +238,7 @@ useGraphControls { forceAtlasS
, hyperdataGraph
, reloadForest
, session
, showTree
, sidePanel
, sidePanelState } = do
edgeConfluence <- T.useBox $ Range.Closed { min: 0.0, max: 1.0 }
......@@ -251,7 +256,6 @@ useGraphControls { forceAtlasS
showEdges <- T.useBox SigmaxT.EShow
showLouvain <- T.useBox false
-- sidePanelState <- T.useBox GT.InitialClosed
showTree <- T.useBox false
sigma <- Sigmax.initSigma
sigmaRef <- R.useRef sigma
......@@ -277,9 +281,3 @@ useGraphControls { forceAtlasS
, sigmaRef
, reloadForest
}
setShowControls :: Record Controls -> Boolean -> Effect Unit
setShowControls { showControls } v = T.write_ v showControls
setShowTree :: Record Controls -> Boolean -> Effect Unit
setShowTree { showTree } v = T.write_ (not v) showTree
......@@ -35,26 +35,27 @@ focusedSidePanel :: T.Box (Maybe (Record SidePanel))
, sideTab :: T.Box GET.SideTab }
focusedSidePanel sidePanel = do
mGraph <- T.useFocused
(maybe Nothing (_.mGraph))
(maybe Nothing _.mGraph)
(\val -> maybe Nothing (\sp -> Just $ sp { mGraph = val })) sidePanel
mMetaData <- T.useFocused
(maybe Nothing (_.mMetaData))
(maybe Nothing _.mMetaData)
(\val -> maybe Nothing (\sp -> Just $ sp { mMetaData = val })) sidePanel
multiSelectEnabled <- T.useFocused
(maybe false (_.multiSelectEnabled))
(maybe false _.multiSelectEnabled)
(\val -> maybe Nothing (\sp -> Just $ sp { multiSelectEnabled = val })) sidePanel
removedNodeIds <- T.useFocused
(maybe Set.empty (_.removedNodeIds))
(maybe Set.empty _.removedNodeIds)
(\val -> maybe Nothing (\sp -> Just $ sp { removedNodeIds = val })) sidePanel
selectedNodeIds <- T.useFocused
(maybe Set.empty (_.selectedNodeIds))
(maybe Set.empty _.selectedNodeIds)
(\val -> maybe Nothing (\sp -> Just $ sp { selectedNodeIds = val })) sidePanel
showControls <- T.useFocused
(maybe false (_.showControls))
(maybe false _.showControls)
(\val -> maybe Nothing (\sp -> Just $ sp { showControls = val })) sidePanel
sideTab <- T.useFocused
(maybe GET.SideTabLegend (_.sideTab))
(maybe GET.SideTabLegend _.sideTab)
(\val -> maybe Nothing (\sp -> Just $ sp { sideTab = val })) sidePanel
pure $ {
mGraph
, mMetaData
......
......@@ -47,7 +47,7 @@ toggleButtonCpt = here.component "toggleButton" cpt
state' <- T.useLive T.unequal state
pure $ H.button { className: "btn btn-outline-" <> style <> " " <> cls state'
, on: {click: onClick}
, on: { click: onClick }
} [ R2.small {} [ H.text (text onMessage offMessage state') ] ]
cls true = "active"
......
......@@ -30,11 +30,8 @@ import Gargantext.Components.Nodes.File (fileLayout)
import Gargantext.Components.Nodes.Frame (frameLayout)
import Gargantext.Components.Nodes.Home (homeLayout)
import Gargantext.Components.Nodes.Lists as Lists
import Gargantext.Components.Nodes.Lists.Types as ListsTypes
import Gargantext.Components.Nodes.Texts as Texts
import Gargantext.Components.SessionLoader (sessionWrapper)
import Gargantext.Components.SimpleLayout (simpleLayout)
import Gargantext.Components.TopBar (handedChooser)
import Gargantext.Components.TopBar as TopBar
import Gargantext.Config (defaultFrontends, defaultBackends)
import Gargantext.Ends (Backend)
......@@ -43,7 +40,6 @@ import Gargantext.Routes as GR
import Gargantext.Sessions (Session, WithSessionContext)
import Gargantext.Types (CorpusId, ListId, NodeID, NodeType(..), SessionId, SidePanelState(..))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Router"
......@@ -156,6 +152,7 @@ forestCpt = here.component "forest" cpt where
, route
, sessions
, showLogin
, showTree
, tasks }
, session } _ = do
session' <- R.useContext session
......@@ -169,6 +166,7 @@ forestCpt = here.component "forest" cpt where
, route
, sessions
, showLogin
, showTree
, tasks } [ renderRoute (Record.merge { session } props) [] ]
sidePanel :: R2.Component (WithSessionContext Props)
......@@ -187,13 +185,16 @@ sidePanelCpt = here.component "sidePanel" cpt where
session' <- R.useContext session
sidePanelState' <- T.useLive T.unequal sidePanelState
let className = "side-panel"
case sidePanelState' of
Opened ->
case route' of
GR.Lists s n -> do
pure $ H.div { className: "side-panel" } [ Lists.sidePanel { session: session'
, sidePanel: sidePanelLists
, sidePanelState } [] ]
pure $ H.div { className }
[ Lists.sidePanel { session: session'
, sidePanel: sidePanelLists
, sidePanelState } [] ]
GR.PGraphExplorer s g -> do
{ mGraph, mMetaData, removedNodeIds, selectedNodeIds, sideTab } <- GEST.focusedSidePanel sidePanelGraph
mGraph' <- T.useLive T.unequal mGraph
......@@ -203,22 +204,23 @@ sidePanelCpt = here.component "sidePanel" cpt where
(Nothing /\ _) -> pure $ H.div {} []
(_ /\ Nothing) -> pure $ H.div {} []
(Just graph /\ Just metaData) -> do
pure $ H.div { className: "side-panel" }
[ GES.sidebar { frontends: defaultFrontends
, graph
, graphId: g
, graphVersion
, metaData
, reloadForest
, removedNodeIds
, selectedNodeIds
, session: session'
, sideTab
} [] ]
pure $ H.div { className }
[ GES.sidebar { frontends: defaultFrontends
, graph
, graphId: g
, graphVersion
, metaData
, reloadForest
, removedNodeIds
, selectedNodeIds
, session: session'
, sideTab
} [] ]
GR.Texts s n -> do
pure $ H.div { className: "side-panel" } [ Texts.sidePanel { session: session'
, sidePanel: sidePanelTexts
, sidePanelState } [] ]
pure $ H.div { className }
[ Texts.sidePanel { session: session'
, sidePanel: sidePanelTexts
, sidePanelState } [] ]
_ -> pure $ H.div {} []
_ -> pure $ H.div {} []
......
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