Commit 08c8d76c authored by Karen Konou's avatar Karen Konou

[WIP] team loader

parent 12d7ffb8
......@@ -73,13 +73,11 @@ getTreeFirstLevel session id = do
liftEffect $ here.log2 "[getTreeFirstLevel] tree first level" tree
pure $ Right tree -- TODO: error handling
getTeam :: Session -> Int -> AffRESTError TeamMember
getTeam :: Session -> Int -> AffRESTError (Array TeamMember)
getTeam session id = do
{ team } <- queryGql session "get team" $ teamQuery `withVars` { id }
liftEffect $ here.log2 "[getTree] data" team
pure $ case A.head team of
Nothing -> Left (CustomError $ "team node id=" <> show id <> " not found")
Just t -> Right t
pure $ Right team
type SharedFolderId = Int
type TeamNodeId = Int
......
......@@ -3,7 +3,12 @@ module Gargantext.Components.Nodes.Team where
import Gargantext.Prelude
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Sessions (Session(..))
import Gargantext.Components.FolderView as FV
import Gargantext.Components.GraphQL.Team (TeamMember)
import Gargantext.Components.GraphQL.Endpoints (getTeam)
import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Sessions (Session)
import Gargantext.Types (ID)
import Gargantext.Utils.Reactix as R2
import Reactix as R
......@@ -22,5 +27,52 @@ teamLayout = R2.leafComponent teamLayoutCpt
teamLayoutCpt :: R.Component Props
teamLayoutCpt = here.component "teamLayout" cpt where
cpt _ _ = do
pure $ H.text "todo"
cpt props _ = do
pure $ R.fragment [
FV.folderView props
, teamLayoutMain props
]
teamLayoutMain :: R2.Leaf Props
teamLayoutMain = R2.leafComponent teamLayoutMainCpt
teamLayoutMainCpt :: R.Component Props
teamLayoutMainCpt = here.component "teamLayoutMain" cpt where
cpt { nodeId, session, boxes } _ = do
useLoader { errorHandler
, loader: loadTeam
, path: { nodeId, session }
, render: \team -> teamLayoutRows { boxes
, team
, nodeId
, session
}
}
where
errorHandler = logRESTError here "teamLayout"
type TeamProps =
( boxes :: Boxes
, nodeId :: ID
, session :: Session
, team :: Array TeamMember )
teamLayoutRows :: R2.Leaf TeamProps
teamLayoutRows = R2.leafComponent teamLayoutRowsCpt
teamLayoutRowsCpt :: R.Component TeamProps
teamLayoutRowsCpt = here.component "teamLayoutRows" cpt where
cpt { team } _ = do
pure $ H.div {} $ map makeTeam team
where
makeTeam { username } = H.p {} [H.text username]
type LoadProps =
(
session :: Session,
nodeId :: Int
)
loadTeam :: Record LoadProps -> AffRESTError (Array TeamMember)
loadTeam { session, nodeId } = getTeam session nodeId
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