Commit 00acf894 authored by James Laver's avatar James Laver

forest works, tree links do not

parent e3928c5a
...@@ -3,7 +3,7 @@ module Gargantext.Components.App where ...@@ -3,7 +3,7 @@ module Gargantext.Components.App where
import Prelude import Prelude
import Data.Array (fromFoldable) import Data.Array (fromFoldable)
import Data.Foldable (intercalate) import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), maybe')
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -12,8 +12,8 @@ import Gargantext.Components.Data.Lang (Lang(..)) ...@@ -12,8 +12,8 @@ import Gargantext.Components.Data.Lang (Lang(..))
import Gargantext.Components.Forest (forest) import Gargantext.Components.Forest (forest)
import Gargantext.Components.GraphExplorer (explorerLayout) import Gargantext.Components.GraphExplorer (explorerLayout)
import Gargantext.Components.Login (login) import Gargantext.Components.Login (login)
import Gargantext.Components.Search.SearchBar as SB -- import Gargantext.Components.Search.SearchBar as SB
import Gargantext.Components.Search.Types (allDatabases) -- import Gargantext.Components.Search.Types (allDatabases)
import Gargantext.Config (defaultFrontends, defaultBackends) import Gargantext.Config (defaultFrontends, defaultBackends)
import Gargantext.Components.Folder (folder) import Gargantext.Components.Folder (folder)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
...@@ -29,6 +29,7 @@ import Gargantext.Router (router) ...@@ -29,6 +29,7 @@ import Gargantext.Router (router)
import Gargantext.Routes (AppRoute(..)) import Gargantext.Routes (AppRoute(..))
import Gargantext.Hooks.Router (useHashRouter) import Gargantext.Hooks.Router (useHashRouter)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Sessions as Sessions
import Gargantext.Sessions (Sessions, useSessions, unSessions) import Gargantext.Sessions (Sessions, useSessions, unSessions)
-- TODO (what does this mean?) -- TODO (what does this mean?)
...@@ -47,37 +48,39 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where ...@@ -47,37 +48,39 @@ appCpt = R.hooksComponent "G.C.App.app" cpt where
showLogin <- R.useState' false showLogin <- R.useState' false
showCorpus <- R.useState' false showCorpus <- R.useState' false
let tree = forestLayout frontends (fst sessions) (fst route) (snd showLogin) let forested = forestLayout frontends (fst sessions) (fst route) (snd showLogin)
let mCurrentRoute = fst route let mCurrentRoute = fst route
let backends = fromFoldable defaultBackends let backends = fromFoldable defaultBackends
let withSession = \sid f -> maybe' (\_ -> forested $ homeLayout EN) f $ Sessions.lookup sid (fst sessions)
pure $ case fst showLogin of pure $ case fst showLogin of
true -> tree $ login { sessions, backends, visible: showLogin } true -> forested $ login { sessions, backends, visible: showLogin }
false -> false ->
case unSessions (fst sessions) of case fst route of
Nothing -> tree $ homeLayout EN Home -> forested $ homeLayout EN
Just session ->
case (fst route) of
Home -> tree $ homeLayout EN
Login -> login { sessions, backends, visible: showLogin } Login -> login { sessions, backends, visible: showLogin }
Folder _ -> tree $ folder {} Folder sid _ -> withSession sid $ \_ -> forested (folder {})
Corpus nodeId -> tree $ corpusLayout { nodeId } Corpus sid nodeId -> withSession sid $ \_ -> forested $ corpusLayout { nodeId }
Texts nodeId -> tree $ textsLayout { nodeId, session } Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session }
Lists nodeId -> tree $ listsLayout { nodeId, session } Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session }
Dashboard _nodeId -> tree $ dashboardLayout {} Dashboard sid _nodeId -> withSession sid $ \session -> forested $ dashboardLayout {}
Annuaire nodeId -> tree $ annuaireLayout { nodeId, session } Annuaire sid nodeId -> withSession sid $ \session -> forested $ annuaireLayout { nodeId, session }
UserPage nodeId -> tree $ userLayout { nodeId, session } UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { nodeId, session }
ContactPage nodeId -> tree $ userLayout { nodeId, session } ContactPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { nodeId, session }
CorpusDocument corpusId listId nodeId -> CorpusDocument sid corpusId listId nodeId ->
tree $ documentLayout { nodeId, listId, session, corpusId: Just corpusId } withSession sid $ \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Just corpusId }
Document listId nodeId -> Document sid listId nodeId ->
tree $ documentLayout { nodeId, listId, session, corpusId: Nothing } withSession sid $
PGraphExplorer graphId -> \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Nothing }
simpleLayout (fst sessions) $ PGraphExplorer sid graphId ->
explorerLayout { graphId, mCurrentRoute, session, sessions, treeId: Nothing, frontends} withSession sid $
\session ->
simpleLayout $
explorerLayout { graphId, mCurrentRoute, session
, sessions: (fst sessions), treeId: Nothing, frontends}
forestLayout :: Frontends -> Sessions -> AppRoute -> R2.Setter Boolean -> R.Element -> R.Element forestLayout :: Frontends -> Sessions -> AppRoute -> R2.Setter Boolean -> R.Element -> R.Element
forestLayout frontends sessions route showLogin child = forestLayout frontends sessions route showLogin child =
R.fragment [ topBar sessions, row main, footer {} ] R.fragment [ topBar {}, row main, footer {} ]
where where
row child' = H.div {className: "row"} [child'] row child' = H.div {className: "row"} [child']
main = main =
......
...@@ -32,7 +32,7 @@ import Gargantext.Hooks.Loader (useLoader) ...@@ -32,7 +32,7 @@ import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Routes (SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (NodeType(..), OrderBy(..), TabType, TabPostQuery(..)) import Gargantext.Types (NodeType(..), OrderBy(..), TabType, TabPostQuery(..))
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -248,16 +248,17 @@ loadPage session {nodeId, tabType, query, listId, corpusId, params: {limit, offs ...@@ -248,16 +248,17 @@ loadPage session {nodeId, tabType, query, listId, corpusId, params: {limit, offs
convOrderBy _ = DateAsc -- TODO convOrderBy _ = DateAsc -- TODO
renderPage :: R.State T.Params -> Record PageLoaderProps -> Array DocumentsView -> R.Element renderPage :: R.State T.Params -> Record PageLoaderProps -> Array DocumentsView -> R.Element
renderPage (_ /\ setTableParams) p res = R.createElement el p [] renderPage (_ /\ setTableParams) p@{session} res = R.createElement el p []
where where
sid = sessionId session
el = R.hooksComponent "RenderPage" cpt el = R.hooksComponent "RenderPage" cpt
gi Favorite = "glyphicon glyphicon-star" gi Favorite = "glyphicon glyphicon-star"
gi _ = "glyphicon glyphicon-star-empty" gi _ = "glyphicon glyphicon-star-empty"
trashStyle Trash = {textDecoration: "line-through"} trashStyle Trash = {textDecoration: "line-through"}
trashStyle _ = {textDecoration: "none"} trashStyle _ = {textDecoration: "none"}
corpusDocument (Just corpusId) = Routes.CorpusDocument corpusId corpusDocument (Just corpusId) = Routes.CorpusDocument sid corpusId
corpusDocument _ = Routes.Document corpusDocument _ = Routes.Document sid
cpt {session, nodeId, corpusId, listId, totalRecords} _children = do cpt {session, nodeId, corpusId, listId, totalRecords} _children = do
localCategories <- R.useState' (mempty :: LocalCategories) localCategories <- R.useState' (mempty :: LocalCategories)
......
...@@ -48,7 +48,7 @@ explorerLayout props = R.createElement explorerLayoutCpt props [] ...@@ -48,7 +48,7 @@ explorerLayout props = R.createElement explorerLayoutCpt props []
explorerLayoutCpt :: R.Component LayoutProps explorerLayoutCpt :: R.Component LayoutProps
explorerLayoutCpt = R.hooksComponent "G.C.GraphExplorer.explorerLayout" cpt explorerLayoutCpt = R.hooksComponent "G.C.GraphExplorer.explorerLayout" cpt
where where
cpt {graphId, mCurrentRoute, treeId, session, frontends} _ = cpt {graphId, mCurrentRoute, treeId, session, sessions, frontends} _ =
useLoader graphId (getNodes session) handler useLoader graphId (getNodes session) handler
where where
handler loaded = explorer {graphId, mCurrentRoute, treeId, session, sessions, graph, frontends} handler loaded = explorer {graphId, mCurrentRoute, treeId, session, sessions, graph, frontends}
......
...@@ -152,8 +152,8 @@ performAction session _ ({tree: NTree (LNode {id}) _} /\ _) (UploadFile fileType ...@@ -152,8 +152,8 @@ performAction session _ ({tree: NTree (LNode {id}) _} /\ _) (UploadFile fileType
------------------------------------------------------------------------ ------------------------------------------------------------------------
mCorpusId :: Maybe AppRoute -> Maybe Int mCorpusId :: Maybe AppRoute -> Maybe Int
mCorpusId (Just (Routes.Corpus id)) = Just id mCorpusId (Just (Routes.Corpus _ id)) = Just id
mCorpusId (Just (Routes.CorpusDocument id _ _)) = Just id mCorpusId (Just (Routes.CorpusDocument _ id _ _)) = Just id
mCorpusId _ = Nothing mCorpusId _ = Nothing
treeView :: Record Props -> R.Element treeView :: Record Props -> R.Element
......
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