Commit db7e16cc authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[toestand] more refactoring work

parent 7ee27ee6
...@@ -4,6 +4,7 @@ import Data.Set as Set ...@@ -4,6 +4,7 @@ import Data.Set as Set
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Toestand as T import Toestand as T
import Gargantext.Ends (Backend(..))
import Gargantext.Sessions as Sessions import Gargantext.Sessions as Sessions
import Gargantext.Sessions (OpenNodes, Sessions) import Gargantext.Sessions (OpenNodes, Sessions)
import Gargantext.Routes (AppRoute(Home)) import Gargantext.Routes (AppRoute(Home))
...@@ -34,10 +35,11 @@ emptyApp = ...@@ -34,10 +35,11 @@ emptyApp =
} }
type Cursors = type Cursors =
{ handed :: T.Cursor Handed { backend :: T.Cursor (Maybe Backend)
, handed :: T.Cursor Handed
, forestOpen :: T.Cursor OpenNodes , forestOpen :: T.Cursor OpenNodes
, reloadRoot :: T.Cursor Int , reloadRoot :: T.Cursor T2.Reload
, reloadForest :: T.Cursor Int , reloadForest :: T.Cursor T2.Reload
, route :: T.Cursor AppRoute , route :: T.Cursor AppRoute
, sessions :: T.Cursor Sessions , sessions :: T.Cursor Sessions
, showCorpus :: T.Cursor Boolean , showCorpus :: T.Cursor Boolean
......
...@@ -13,12 +13,12 @@ here :: R2.Here ...@@ -13,12 +13,12 @@ here :: R2.Here
here = R2.here "Gargantext.Components.Footer" here = R2.here "Gargantext.Components.Footer"
--------------------------------------------------------------------------- ---------------------------------------------------------------------------
type FooterProps s = ( session :: s ) type FooterProps = ( )
footer :: forall cell c. T.Read cell c => Record (FooterProps cell) -> R.Element footer :: R2.Component FooterProps
footer props = R.createElement footerCpt props [] footer = R.createElement footerCpt
footerCpt :: forall cell c. T.Read cell c => R.Component (FooterProps cell) footerCpt :: R.Component FooterProps
footerCpt = here.component "footer" cpt where footerCpt = here.component "footer" cpt where
cpt { session } _ = cpt { } _ = do
pure $ H.div { className: "container" } [ H.hr {}, H.footer {} [] ] pure $ H.div { className: "container" } [ H.hr {}, H.footer {} [] ]
...@@ -37,12 +37,12 @@ type Common = ...@@ -37,12 +37,12 @@ type Common =
( frontends :: Frontends ( frontends :: Frontends
, handed :: T.Cursor Handed , handed :: T.Cursor Handed
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, route :: AppRoute , route :: T.Cursor AppRoute
, tasks :: T.Cursor (Maybe GAT.Reductor) , tasks :: T.Cursor (Maybe GAT.Reductor)
) )
type LayoutProps = type LayoutProps =
( backend :: T.Cursor Backend ( backend :: T.Cursor (Maybe Backend)
, reloadForest :: T.Cursor T2.Reload , reloadForest :: T.Cursor T2.Reload
, sessions :: T.Cursor Sessions , sessions :: T.Cursor Sessions
, showLogin :: T.Cursor Boolean , showLogin :: T.Cursor Boolean
...@@ -73,13 +73,13 @@ forestCpt = here.component "forest" cpt where ...@@ -73,13 +73,13 @@ forestCpt = here.component "forest" cpt where
, sessions , sessions
, showLogin , showLogin
, tasks } _ = do , tasks } _ = do
-- NOTE: this is a hack to reload the forest on demand
tasks' <- GAT.useTasks reloadRoot reloadForest tasks' <- GAT.useTasks reloadRoot reloadForest
R.useEffect' $ do R.useEffect' $ do
T2.write_ (Just tasks') tasks T2.write_ (Just tasks') tasks
handed' <- T.useLive T.unequal handed handed' <- T.useLive T.unequal handed
reloadForest' <- T.useLive T.unequal reloadForest reloadForest' <- T.useLive T.unequal reloadForest
reloadRoot' <- T.useLive T.unequal reloadRoot reloadRoot' <- T.useLive T.unequal reloadRoot
route' <- T.useLive T.unequal route
forestOpen' <- T.useLive T.unequal forestOpen forestOpen' <- T.useLive T.unequal forestOpen
sessions' <- T.useLive T.unequal sessions sessions' <- T.useLive T.unequal sessions
-- TODO If `reloadForest` is set, `reload` state should be updated -- TODO If `reloadForest` is set, `reload` state should be updated
...@@ -88,14 +88,14 @@ forestCpt = here.component "forest" cpt where ...@@ -88,14 +88,14 @@ forestCpt = here.component "forest" cpt where
-- R.setRef tasks $ Just tasks' -- R.setRef tasks $ Just tasks'
-- GUR.initializeI reloadForest reload -- GUR.initializeI reloadForest reload
R2.useCache R2.useCache
( frontends /\ route /\ sessions' /\ handed' /\ forestOpen' ( frontends /\ route' /\ sessions' /\ handed' /\ forestOpen'
/\ reloadForest' /\ reloadRoot' /\ (fst tasks').storage ) /\ reloadForest' /\ reloadRoot' /\ (fst tasks').storage )
(cp handed' sessions' tasks') (cp handed' sessions' tasks')
where where
common = RX.pick props :: Record Common common = RX.pick props :: Record Common
cp handed' sessions' tasks' _ = cp handed' sessions' tasks' _ =
pure $ H.div { className: "forest" } pure $ H.div { className: "forest" }
(A.cons (plus handed' showLogin backend) (trees handed' sessions' tasks')) (A.cons (plus handed' showLogin) (trees handed' sessions' tasks'))
trees handed' sessions' tasks' = (tree handed' tasks') <$> unSessions sessions' trees handed' sessions' tasks' = (tree handed' tasks') <$> unSessions sessions'
tree handed' tasks' s@(Session {treeId}) = tree handed' tasks' s@(Session {treeId}) =
treeLoader { forestOpen treeLoader { forestOpen
...@@ -108,8 +108,8 @@ forestCpt = here.component "forest" cpt where ...@@ -108,8 +108,8 @@ forestCpt = here.component "forest" cpt where
, session: s , session: s
, tasks } [] , tasks } []
plus :: Handed -> T.Cursor Boolean -> T.Cursor Backend -> R.Element plus :: Handed -> T.Cursor Boolean -> R.Element
plus handed showLogin backend = H.div { className: "row" } plus handed showLogin = H.div { className: "row" }
[ H.button { className: buttonClass [ H.button { className: buttonClass
, on: { click } , on: { click }
, title } , title }
...@@ -131,18 +131,19 @@ plus handed showLogin backend = H.div { className: "row" } ...@@ -131,18 +131,19 @@ plus handed showLogin backend = H.div { className: "row" }
forestLayout :: R2.Component LayoutProps forestLayout :: R2.Component LayoutProps
forestLayout props = R.createElement forestLayoutCpt props forestLayout = R.createElement forestLayoutCpt
forestLayoutCpt :: R.Component LayoutProps forestLayoutCpt :: R.Component LayoutProps
forestLayoutCpt = here.component "forestLayout" cpt where forestLayoutCpt = here.component "forestLayout" cpt where
cpt props@{ handed } children = cpt props@{ handed } children =
pure $ R.fragment pure $ R.fragment
[ topBar { handed } [], forestLayoutMain props children ] [ topBar { handed } []
, forestLayoutMain props children ]
-- Renders its first child component in the top bar and the rest in -- Renders its first child component in the top bar and the rest in
-- the main view. -- the main view.
forestLayoutWithTopBar :: R2.Component LayoutProps forestLayoutWithTopBar :: R2.Component LayoutProps
forestLayoutWithTopBar props = R.createElement forestLayoutWithTopBarCpt props forestLayoutWithTopBar = R.createElement forestLayoutWithTopBarCpt
forestLayoutWithTopBarCpt :: R.Component LayoutProps forestLayoutWithTopBarCpt :: R.Component LayoutProps
forestLayoutWithTopBarCpt = here.component "forestLayoutWithTopBar" cpt where forestLayoutWithTopBarCpt = here.component "forestLayoutWithTopBar" cpt where
...@@ -154,14 +155,14 @@ forestLayoutWithTopBarCpt = here.component "forestLayoutWithTopBar" cpt where ...@@ -154,14 +155,14 @@ forestLayoutWithTopBarCpt = here.component "forestLayoutWithTopBar" cpt where
, forestLayoutMain props mainChildren ] , forestLayoutMain props mainChildren ]
forestLayoutMain :: R2.Component LayoutProps forestLayoutMain :: R2.Component LayoutProps
forestLayoutMain props = R.createElement forestLayoutMainCpt props forestLayoutMain = R.createElement forestLayoutMainCpt
forestLayoutMainCpt :: R.Component LayoutProps forestLayoutMainCpt :: R.Component LayoutProps
forestLayoutMainCpt = here.component "forestLayoutMain" cpt where forestLayoutMainCpt = here.component "forestLayoutMain" cpt where
cpt props children = pure $ forestLayoutRaw props [ mainPage {} children ] cpt props children = pure $ forestLayoutRaw props [ mainPage {} children ]
forestLayoutRaw :: R2.Component LayoutProps forestLayoutRaw :: R2.Component LayoutProps
forestLayoutRaw props = R.createElement forestLayoutRawCpt props forestLayoutRaw = R.createElement forestLayoutRawCpt
forestLayoutRawCpt :: R.Component LayoutProps forestLayoutRawCpt :: R.Component LayoutProps
forestLayoutRawCpt = here.component "forestLayoutRaw" cpt where forestLayoutRawCpt = here.component "forestLayoutRaw" cpt where
......
...@@ -55,12 +55,15 @@ type Universal = ...@@ -55,12 +55,15 @@ type Universal =
type Global = type Global =
( frontends :: Frontends ( frontends :: Frontends
, handed :: Handed , handed :: Handed
, route :: AppRoute , route :: T.Cursor AppRoute
| Universal ) | Universal )
-- Shared by every component here -- Shared by every component here
type Common = type Common = (
( forestOpen :: T.Cursor OpenNodes, reload :: T.Cursor T2.Reload | Global ) forestOpen :: T.Cursor OpenNodes
, reload :: T.Cursor T2.Reload
| Global
)
type LoaderProps = ( session :: Session, root :: ID | Common ) type LoaderProps = ( session :: Session, root :: ID | Common )
......
...@@ -54,7 +54,7 @@ type NodeMainSpanProps = ...@@ -54,7 +54,7 @@ type NodeMainSpanProps =
, name :: Name , name :: Name
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, route :: Routes.AppRoute , route :: T.Cursor Routes.AppRoute
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit)) , setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
, tasks :: T.Cursor (Maybe GAT.Reductor) , tasks :: T.Cursor (Maybe GAT.Reductor)
| CommonProps | CommonProps
...@@ -91,13 +91,14 @@ nodeMainSpanCpt = here.component "nodeMainSpan" cpt ...@@ -91,13 +91,14 @@ nodeMainSpanCpt = here.component "nodeMainSpan" cpt
, setPopoverRef , setPopoverRef
, tasks , tasks
} _ = do } _ = do
route' <- T.useLive T.unequal route
-- only 1 popup at a time is allowed to be opened -- only 1 popup at a time is allowed to be opened
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile) droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false isDragOver <- R.useState' false
popoverRef <- R.useRef null popoverRef <- R.useRef null
R.useEffect' $ do R.useEffect' $ do
R.setRef setPopoverRef $ Just $ Popover.setOpen popoverRef R.setRef setPopoverRef $ Just $ Popover.setOpen popoverRef
let isSelected = Just route == Routes.nodeTypeAppRoute nodeType (sessionId session) id let isSelected = Just route' == Routes.nodeTypeAppRoute nodeType (sessionId session) id
tasks' <- T.read tasks tasks' <- T.read tasks
......
...@@ -45,11 +45,11 @@ here :: R2.Here ...@@ -45,11 +45,11 @@ here :: R2.Here
here = R2.here "Gargantext.Components.GraphExplorer" here = R2.here "Gargantext.Components.GraphExplorer"
type LayoutProps = ( type LayoutProps = (
backend :: T.Cursor Backend backend :: T.Cursor (Maybe Backend)
, frontends :: Frontends , frontends :: Frontends
, graphId :: GET.GraphId , graphId :: GET.GraphId
, handed :: T.Cursor Types.Handed , handed :: T.Cursor Types.Handed
, route :: AppRoute , route :: T.Cursor AppRoute
, session :: Session , session :: Session
, sessions :: T.Cursor Sessions , sessions :: T.Cursor Sessions
, showLogin :: T.Cursor Boolean , showLogin :: T.Cursor Boolean
...@@ -95,9 +95,7 @@ explorer props = R.createElement explorerCpt props [] ...@@ -95,9 +95,7 @@ explorer props = R.createElement explorerCpt props []
explorerCpt :: R.Component Props explorerCpt :: R.Component Props
explorerCpt = here.component "explorer" cpt explorerCpt = here.component "explorer" cpt
where where
cpt props@{ tasks cpt props@{ backend
, backend
, route
, frontends , frontends
, graph , graph
, graphId , graphId
...@@ -105,9 +103,11 @@ explorerCpt = here.component "explorer" cpt ...@@ -105,9 +103,11 @@ explorerCpt = here.component "explorer" cpt
, handed , handed
, hyperdataGraph , hyperdataGraph
, mMetaData , mMetaData
, route
, session , session
, sessions , sessions
, showLogin , showLogin
, tasks
} _ = do } _ = do
handed' <- T.useLive T.unequal handed handed' <- T.useLive T.unequal handed
...@@ -120,6 +120,7 @@ explorerCpt = here.component "explorer" cpt ...@@ -120,6 +120,7 @@ explorerCpt = here.component "explorer" cpt
dataRef <- R.useRef graph dataRef <- R.useRef graph
graphRef <- R.useRef null graphRef <- R.useRef null
graphVersionRef <- R.useRef (GUR.value graphVersion) graphVersionRef <- R.useRef (GUR.value graphVersion)
-- reloadForest <- T2.useCursed $ T2.Ready 0
reloadForest <- T2.useCursed 0 reloadForest <- T2.useCursed 0
-- reloadForest <- GUR.newIInitialized reloadForest -- reloadForest <- GUR.newIInitialized reloadForest
controls <- Controls.useGraphControls { forceAtlasS controls <- Controls.useGraphControls { forceAtlasS
...@@ -250,13 +251,13 @@ explorerCpt = here.component "explorer" cpt ...@@ -250,13 +251,13 @@ explorerCpt = here.component "explorer" cpt
Sidebar.sidebar (Record.merge props { metaData }) Sidebar.sidebar (Record.merge props { metaData })
type TreeProps = ( type TreeProps = (
backend :: T.Cursor Backend backend :: T.Cursor (Maybe Backend)
, forestOpen :: T.Cursor OpenNodes , forestOpen :: T.Cursor OpenNodes
, frontends :: Frontends , frontends :: Frontends
, handed :: T.Cursor Types.Handed , handed :: T.Cursor Types.Handed
, reload :: T.Cursor T2.Reload , reload :: T.Cursor T2.Reload
, reloadForest :: T.Cursor T2.Reload , reloadForest :: T.Cursor T2.Reload
, route :: AppRoute , route :: T.Cursor AppRoute
, sessions :: T.Cursor Sessions , sessions :: T.Cursor Sessions
, show :: Boolean , show :: Boolean
, showLogin :: T.Cursor Boolean , showLogin :: T.Cursor Boolean
......
...@@ -31,9 +31,9 @@ here = R2.here "Gargantext.Components.Login" ...@@ -31,9 +31,9 @@ here = R2.here "Gargantext.Components.Login"
-- and ask for login (modal) or account creation after 15 mn when user -- and ask for login (modal) or account creation after 15 mn when user
-- if not logged user can not save his work -- if not logged user can not save his work
type Props = type Props = (
( backends :: Array Backend backend :: T.Cursor (Maybe Backend)
, backend :: T.Cursor (Maybe Backend) , backends :: Array Backend
, sessions :: T.Cursor Sessions , sessions :: T.Cursor Sessions
, visible :: T.Cursor Boolean , visible :: T.Cursor Boolean
) )
...@@ -43,11 +43,11 @@ login props = R.createElement loginCpt props [] ...@@ -43,11 +43,11 @@ login props = R.createElement loginCpt props []
loginCpt :: R.Component Props loginCpt :: R.Component Props
loginCpt = here.component "login" cpt where loginCpt = here.component "login" cpt where
cpt props@{ visible, sessions } _ = do cpt props@{ backend, sessions, visible } _ = do
b <- T.useLive T.unequal props.backend b <- T.useLive T.unequal backend
pure $ modal { visible } (inner b) where pure $ modal { visible } (inner b) where
inner Nothing = chooser props inner Nothing = chooser props
inner (Just b) = form { sessions, visible, backend: b } inner (Just b) = form { backend: b, sessions, visible }
chooser :: R2.Leaf Props chooser :: R2.Leaf Props
chooser props = R.createElement chooserCpt props [] chooser props = R.createElement chooserCpt props []
......
...@@ -258,7 +258,7 @@ tableContainerCpt { dispatch ...@@ -258,7 +258,7 @@ tableContainerCpt { dispatch
type CommonProps = ( type CommonProps = (
afterSync :: Unit -> Aff Unit afterSync :: Unit -> Aff Unit
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, sidePanelTriggers :: Record NT.SidePanelTriggers , sidePanelTriggers :: Record NT.SidePanelTriggers
, tabNgramType :: CTabNgramType , tabNgramType :: CTabNgramType
......
...@@ -140,6 +140,7 @@ import Gargantext.Sessions (Session, get, post, put) ...@@ -140,6 +140,7 @@ import Gargantext.Sessions (Session, get, post, put)
import Gargantext.Types (AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), ListId, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..)) import Gargantext.Types (AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), ListId, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..))
import Gargantext.Utils.KarpRabin (indicesOfAny) import Gargantext.Utils.KarpRabin (indicesOfAny)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
here :: R2.Here here :: R2.Here
...@@ -1179,7 +1180,7 @@ chartsAfterSync :: forall props discard. ...@@ -1179,7 +1180,7 @@ chartsAfterSync :: forall props discard.
} }
-> T.Cursor (Maybe GAT.Reductor) -> T.Cursor (Maybe GAT.Reductor)
-> Int -> Int
-> T.Cursor (T2.InitReload T.Cursor) -> T.Cursor T2.Reload
-> discard -> discard
-> Aff Unit -> Aff Unit
chartsAfterSync path' tasks nodeId reloadForest _ = do chartsAfterSync path' tasks nodeId reloadForest _ = do
...@@ -1189,7 +1190,9 @@ chartsAfterSync path' tasks nodeId reloadForest _ = do ...@@ -1189,7 +1190,9 @@ chartsAfterSync path' tasks nodeId reloadForest _ = do
mT <- T.read tasks mT <- T.read tasks
case mT of case mT of
Nothing -> log "[chartsAfterSync] tasks is Nothing" Nothing -> log "[chartsAfterSync] tasks is Nothing"
Just tasks' -> snd tasks' (GAT.Insert nodeId task) *> T2.reload reloadForest Just tasks' -> do
snd tasks' (GAT.Insert nodeId task) -- *> T2.reload reloadForest
GUR.bumpCursor reloadForest
postNgramsChartsAsync :: forall s. CoreParams s -> Aff AsyncTaskWithType postNgramsChartsAsync :: forall s. CoreParams s -> Aff AsyncTaskWithType
postNgramsChartsAsync { listIds, nodeId, session, tabType } = do postNgramsChartsAsync { listIds, nodeId, session, tabType } = do
......
...@@ -55,7 +55,7 @@ type TabsProps = ...@@ -55,7 +55,7 @@ type TabsProps =
, contactData :: ContactData , contactData :: ContactData
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sidePanelTriggers :: Record LTypes.SidePanelTriggers , sidePanelTriggers :: Record LTypes.SidePanelTriggers
...@@ -130,7 +130,7 @@ type NTCommon = ...@@ -130,7 +130,7 @@ type NTCommon =
( cacheState :: R.State LTypes.CacheState ( cacheState :: R.State LTypes.CacheState
, defaultListId :: Int , defaultListId :: Int
, nodeId :: Int , nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sidePanelTriggers :: Record LTypes.SidePanelTriggers , sidePanelTriggers :: Record LTypes.SidePanelTriggers
......
...@@ -154,7 +154,7 @@ listElement = H.li { className: "list-group-item justify-content-between" } ...@@ -154,7 +154,7 @@ listElement = H.li { className: "list-group-item justify-content-between" }
type LayoutProps = type LayoutProps =
( frontends :: Frontends ( frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, tasks :: T.Cursor (Maybe GAT.Reductor) , tasks :: T.Cursor (Maybe GAT.Reductor)
......
...@@ -4,7 +4,7 @@ module Gargantext.Components.Nodes.Annuaire.User.Contact ...@@ -4,7 +4,7 @@ module Gargantext.Components.Nodes.Annuaire.User.Contact
) where ) where
import Gargantext.Prelude import Gargantext.Prelude
( Unit, bind, const, discard, pure, show, ($), (<$>), (*>), (<<<), (<>) ) ( Unit, bind, const, discard, pure, show, void, ($), (<$>), (*>), (<<<), (<>) )
import Data.Lens as L import Data.Lens as L
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -26,6 +26,7 @@ import Gargantext.Routes as Routes ...@@ -26,6 +26,7 @@ import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, get, put, sessionId) import Gargantext.Sessions (Session, get, put, sessionId)
import Gargantext.Types (NodeType(..)) import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
here :: R2.Here here :: R2.Here
...@@ -134,12 +135,12 @@ type BasicProps = ...@@ -134,12 +135,12 @@ type BasicProps =
) )
type ReloadProps = type ReloadProps =
( reloadForest :: T.Cursor (T2.InitReload T.Cursor) ( reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
| BasicProps | BasicProps
) )
type LayoutProps = ( session :: T.Cursor (Maybe Session) | ReloadProps ) type LayoutProps = ( session :: Session | ReloadProps )
type KeyLayoutProps = ( key :: String, session :: Session | ReloadProps ) type KeyLayoutProps = ( key :: String, session :: Session | ReloadProps )
...@@ -150,12 +151,12 @@ type AnnuaireLayoutProps = ( annuaireId :: Int, session :: Session | ReloadProps ...@@ -150,12 +151,12 @@ type AnnuaireLayoutProps = ( annuaireId :: Int, session :: Session | ReloadProps
type AnnuaireKeyLayoutProps = ( annuaireId :: Int | KeyLayoutProps ) type AnnuaireKeyLayoutProps = ( annuaireId :: Int | KeyLayoutProps )
contactLayout :: R2.Leaf AnnuaireLayoutProps contactLayout :: R2.Component AnnuaireLayoutProps
contactLayout props = R.createElement contactLayoutCpt props [] contactLayout = R.createElement contactLayoutCpt
contactLayoutCpt :: R.Component AnnuaireLayoutProps contactLayoutCpt :: R.Component AnnuaireLayoutProps
contactLayoutCpt = here.component "contactLayout" cpt where contactLayoutCpt = here.component "contactLayout" cpt where
cpt { annuaireId, reloadRoot, tasks, frontends, nodeId, session, reloadForest } _ = cpt { annuaireId, frontends, nodeId, reloadForest, reloadRoot, session, tasks } _ = do
pure $ pure $
contactLayoutWithKey contactLayoutWithKey
{ annuaireId, tasks, frontends, key, nodeId { annuaireId, tasks, frontends, key, nodeId
...@@ -167,8 +168,13 @@ contactLayoutWithKey props = R.createElement contactLayoutWithKeyCpt props [] ...@@ -167,8 +168,13 @@ contactLayoutWithKey props = R.createElement contactLayoutWithKeyCpt props []
contactLayoutWithKeyCpt :: R.Component AnnuaireKeyLayoutProps contactLayoutWithKeyCpt :: R.Component AnnuaireKeyLayoutProps
contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where
cpt { annuaireId, reloadRoot, tasks, frontends cpt { annuaireId
, nodeId, session, reloadForest } _ = do , frontends
, reloadForest
, reloadRoot
, nodeId
, session
, tasks } _ = do
reload <- T.useCell T2.newReload reload <- T.useCell T2.newReload
_ <- T.useLive T.unequal reload _ <- T.useLive T.unequal reload
cacheState <- R.useState' LT.CacheOn cacheState <- R.useState' LT.CacheOn
......
...@@ -53,7 +53,7 @@ type TabsProps = ( ...@@ -53,7 +53,7 @@ type TabsProps = (
, contactData :: ContactData' , contactData :: ContactData'
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sidePanelTriggers :: Record LTypes.SidePanelTriggers , sidePanelTriggers :: Record LTypes.SidePanelTriggers
...@@ -135,7 +135,7 @@ type NgramsViewTabsProps = ( ...@@ -135,7 +135,7 @@ type NgramsViewTabsProps = (
, defaultListId :: Int , defaultListId :: Int
, mode :: Mode , mode :: Mode
, nodeId :: Int , nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sidePanelTriggers :: Record LTypes.SidePanelTriggers , sidePanelTriggers :: Record LTypes.SidePanelTriggers
......
...@@ -76,7 +76,7 @@ topBarCpt = here.component "topBar" cpt ...@@ -76,7 +76,7 @@ topBarCpt = here.component "topBar" cpt
type CommonProps = ( type CommonProps = (
nodeId :: Int nodeId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sessionUpdate :: Session -> Effect Unit , sessionUpdate :: Session -> Effect Unit
......
...@@ -37,7 +37,7 @@ type Props = ( ...@@ -37,7 +37,7 @@ type Props = (
cacheState :: R.State CacheState cacheState :: R.State CacheState
, corpusData :: CorpusData , corpusData :: CorpusData
, corpusId :: Int , corpusId :: Int
, reloadForest :: T.Cursor (T2.InitReload T.Cursor) , reloadForest :: T.Cursor T2.Reload
, reloadRoot :: T.Cursor T2.Reload , reloadRoot :: T.Cursor T2.Reload
, session :: Session , session :: Session
, sidePanelTriggers :: Record SidePanelTriggers , sidePanelTriggers :: Record SidePanelTriggers
......
This diff is collapsed.
-- | A component that loads the session specified in the route and provides it to its child. -- | A component that loads the session specified in the route and provides it to its child.
-- | -- |
-- | If the session cannot be loaded, displays the homepage. -- | If the session cannot be loaded, displays the homepage.
module Gargantext.Components.SessionLoader where module Gargantext.Components.SessionLoader
where
import Prelude (($), (<$>)) import Prelude (($), (<$>))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
...@@ -16,17 +17,19 @@ here :: R2.Here ...@@ -16,17 +17,19 @@ here :: R2.Here
here = R2.here "Gargantext.Components.SessionWrapper" here = R2.here "Gargantext.Components.SessionWrapper"
type Props sessions = type Props sessions =
( sessionId :: SessionId (
, sessions :: sessions fallback :: R.Element
, provider :: R.Provider Session , provider :: R.Provider Session
, fallback :: R.Element ) , sessionId :: SessionId
, sessions :: sessions
)
sessionWrapper :: forall s. T.Read s Sessions => R2.Component (Props s) sessionWrapper :: forall s. T.Read s Sessions => R2.Component (Props s)
sessionWrapper = R.createElement sessionWrapperCpt sessionWrapper = R.createElement sessionWrapperCpt
sessionWrapperCpt :: forall s. T.Read s Sessions => R.Component (Props s) sessionWrapperCpt :: forall s. T.Read s Sessions => R.Component (Props s)
sessionWrapperCpt = here.component "sessionWrapper" cpt where sessionWrapperCpt = here.component "sessionWrapper" cpt where
cpt { sessionId, sessions, provider, fallback } content = cpt { fallback, provider, sessionId, sessions } content =
cp <$> T.useLive T.unequal sessions where cp <$> T.useLive T.unequal sessions where
cp sessions' = c $ Sessions.lookup sessionId sessions' where cp sessions' = c $ Sessions.lookup sessionId sessions' where
c (Just session) = (R.provide provider session content) c (Just session) = (R.provide provider session content)
......
...@@ -23,6 +23,9 @@ bump (_ /\ setReload) = setReload (_ + 1) ...@@ -23,6 +23,9 @@ bump (_ /\ setReload) = setReload (_ + 1)
bumpCursor :: T.Cursor Reload -> Effect Unit bumpCursor :: T.Cursor Reload -> Effect Unit
bumpCursor c = T2.modify_ (_ + 1) c bumpCursor c = T2.modify_ (_ + 1) c
bumpCell :: T.Cell Reload -> Effect Unit
bumpCell c = T2.modify_ (_ + 1) c
value :: ReloadS -> Reload value :: ReloadS -> Reload
value (val /\ _) = val value (val /\ _) = val
......
...@@ -5,7 +5,7 @@ module Gargantext.Utils.Toestand ...@@ -5,7 +5,7 @@ module Gargantext.Utils.Toestand
, write_, modify_ , write_, modify_
) where ) where
import Prelude (class Ord, Unit, bind, identity, pure, unit, void, ($), (+), (>>=)) import Prelude (class Eq, class Ord, Unit, bind, identity, pure, unit, void, ($), (+), (>>=))
import Data.Set as Set import Data.Set as Set
import Data.Set (Set) import Data.Set (Set)
import Effect (Effect) import Effect (Effect)
......
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