[list selection] prepare for list tree rendering

parent dc563aa7
Pipeline #1764 failed with stage
......@@ -22,7 +22,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Share as Share
import Gargantext.Components.Forest.Tree.Node.Action.Update (updateRequest)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadArbitraryFile, uploadFile)
import Gargantext.Components.Forest.Tree.Node.Box (nodePopupView)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..), fTreeID)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..), ID, fTreeID)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..))
import Gargantext.Config.REST (RESTError)
import Gargantext.Config.Utils (handleRESTError)
......@@ -70,8 +70,8 @@ folderViewCpt = here.component "folderViewCpt" cpt where
, boxes
, folders
, nodeId
, session
, reload
, session
, setPopoverRef } }
where
errorHandler err = here.log2 "[folderView] RESTError" err
......
......@@ -3,9 +3,7 @@ module Gargantext.Components.FolderView.Box where
import Gargantext.Prelude
import DOM.Simple as DOM
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), settingsBox)
import Gargantext.Components.Forest.Tree.Node.Tools (prettyNodeType)
import Gargantext.Types (ID, Name)
import Gargantext.Types as GT
......@@ -13,7 +11,6 @@ import Gargantext.Utils.Glyphicon (glyphicon)
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.FolderView.Box"
......@@ -25,12 +22,11 @@ type NodePopupProps =
, onPopoverClose :: DOM.Element -> Effect Unit
)
nodePopupView :: Record NodePopupProps -> R.Element
nodePopupView props = R.createElement nodePopupCpt props []
nodePopupCpt :: R.Component NodePopupProps
nodePopupCpt = here.component "nodePopupView" cpt where
cpt props@{ id, name, nodeType } _ = do
nodePopupView :: R2.Leaf NodePopupProps
nodePopupView props = R.createElement nodePopupViewCpt props []
nodePopupViewCpt :: R.Component NodePopupProps
nodePopupViewCpt = here.component "nodePopupView" cpt where
cpt props _ = do
pure $ H.div tooltipProps
[ H.div { className: "popup-container" }
......@@ -43,7 +39,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
tooltipProps = { id: "node-popup-tooltip", title: "Node settings"
, data: { toggle: "tooltip", placement: "right" } }
panelHeading props@{id, name, nodeType } =
panelHeading props@{ nodeType } =
H.div { className: "card-header" }
[ R2.row
[ H.div { className: "col-4" }
......@@ -53,5 +49,4 @@ nodePopupCpt = here.component "nodePopupView" cpt where
[ H.span { className: "text-primary center" } [ H.text props.name ] ]
, H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover props }, title: "Close"
, className: glyphicon "window-close" } [] ]]] where
SettingsBox { edit, doc, buttons } = settingsBox nodeType
, className: glyphicon "window-close" } [] ]]]
......@@ -64,7 +64,8 @@ type NodeProps =
| Common )
type TreeProps =
( tree :: FTree
( root :: ID
, tree :: FTree
| NodeProps )
type ChildrenTreeProps =
......@@ -91,8 +92,9 @@ type NSCommon =
-- way. This function is only called by functions in this module, so
-- we just have to careful in what we pass.
type ChildLoaderProps =
( id :: ID
( id :: ID
, render :: R2.Leaf TreeProps
, root :: ID
| NodeProps )
type PerformActionProps =
......@@ -118,7 +120,7 @@ treeLoaderCpt = here.component "treeLoader" cpt where
loaded tree' = tree props where
props = Record.merge common extra where
common = RecordE.pick p :: Record Common
extra = { tree: tree', reloadTree: p.reload, session }
extra = { reloadTree: p.reload, root, session, tree: tree' }
errorHandler err = here.log2 "[treeLoader] RESTError" err
getNodeTree :: Session -> ID -> Aff (Either RESTError FTree)
......@@ -135,6 +137,7 @@ treeCpt = here.component "tree" cpt where
, frontends
, handed
, reload
, root
, session
, tree: NTree (LNode { id, name, nodeType }) children } _ = do
setPopoverRef <- R.useRef Nothing
......@@ -150,6 +153,7 @@ treeCpt = here.component "tree" cpt where
, name
, nodeType
, reload
, root
, session
, setPopoverRef }
[ renderChildren (Record.merge p { childProps: { children', folderOpen, render: tree } } ) [] ]
......@@ -186,13 +190,14 @@ renderTreeChildren = R.createElement renderTreeChildrenCpt
renderTreeChildrenCpt :: R.Component ChildrenTreeProps
renderTreeChildrenCpt = here.component "renderTreeChildren" cpt where
cpt p@{ childProps: { children'
, render } } _ = do
, render }
, root } _ = do
pure $ R.fragment (map renderChild children')
where
nodeProps = RecordE.pick p :: Record NodeProps
renderChild (NTree (LNode {id: cId}) _) = childLoader props [] where
props = Record.merge nodeProps { id: cId, render }
props = Record.merge nodeProps { id: cId, render, root }
childLoader :: R2.Component ChildLoaderProps
childLoader = R.createElement childLoaderCpt
......@@ -200,7 +205,8 @@ childLoaderCpt :: R.Component ChildLoaderProps
childLoaderCpt = here.component "childLoader" cpt where
cpt p@{ boxes: { reloadRoot }
, reloadTree
, render } _ = do
, render
, root } _ = do
reload <- T.useBox T2.newReload
let reloads = [ reload, reloadRoot, reloadTree ]
cache <- (A.cons p.id) <$> traverse (T.useLive T.unequal) reloads
......@@ -213,7 +219,7 @@ childLoaderCpt = here.component "childLoader" cpt where
fetch _ = getNodeTreeFirstLevel p.session p.id
paint reload tree' = render (Record.merge base extra) where
base = nodeProps { reload = reload }
extra = { tree: tree' }
extra = { root, tree: tree' }
nodeProps = RecordE.pick p :: Record NodeProps
closePopover { setPopoverRef } =
......
......@@ -51,6 +51,7 @@ type NodeMainSpanProps =
, name :: Name
, nodeType :: GT.NodeType
, reload :: T2.ReloadS
, root :: ID
, session :: Session
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
)
......
module Gargantext.Components.Forest.Tree.Node.Action where
import Gargantext.Prelude
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut, SubTreeParams(..))
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), glyphiconNodeAction)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType, UploadFileBlob)
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (UpdateNodeParams)
import Gargantext.Components.Forest.Tree.Node.Action.Contact.Types (AddContactParams)
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (UpdateNodeParams)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType, UploadFileBlob)
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), glyphiconNodeAction)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (ID)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut, SubTreeParams(..))
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
import Gargantext.Types as GT
type Props =
( dispatch :: Action -> Aff Unit
, id :: Int
, id :: ID
, nodeType :: GT.NodeType
, session :: Session
)
......
......@@ -21,7 +21,7 @@ import Gargantext.Components.Lang (Lang(..))
import Gargantext.Components.ListSelection as ListSelection
import Gargantext.Config.REST (RESTError)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, postWwwUrlencoded)
import Gargantext.Sessions (Session(..), postWwwUrlencoded)
import Gargantext.Types (NodeType(..), ID)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
......@@ -49,8 +49,10 @@ actionUpload :: R2.Component ActionUpload
actionUpload = R.createElement actionUploadCpt
actionUploadCpt :: R.Component ActionUpload
actionUploadCpt = here.component "actionUpload" cpt where
cpt { nodeType: Corpus, dispatch, id, session } _ = pure $ uploadFileView {dispatch, id, nodeType: GT.Corpus, session}
cpt { nodeType: NodeList, dispatch, id, session } _ = pure $ uploadTermListView {dispatch, id, nodeType: GT.NodeList, session}
cpt { nodeType: Corpus, dispatch, id, session } _ =
pure $ uploadFileView { dispatch, id, nodeType: GT.Corpus, session }
cpt { nodeType: NodeList, dispatch, id, session } _ =
pure $ uploadTermListView { dispatch, id, nodeType: GT.NodeList, session }
cpt props@{ nodeType: _ } _ = pure $ actionUploadOther props []
{-
......@@ -88,13 +90,14 @@ uploadFileView props = R.createElement uploadFileViewCpt props []
uploadFileViewCpt :: R.Component Props
uploadFileViewCpt = here.component "uploadFileView" cpt
where
cpt {dispatch, id, nodeType} _ = do
cpt { dispatch, id, nodeType, session } _ = do
-- mFile :: R.State (Maybe UploadFile) <- R.useState' Nothing
mFile <- T.useBox (Nothing :: Maybe UploadFile)
fileType <- T.useBox CSV
lang <- T.useBox EN
selection <- T.useBox ListSelection.MyListsFirst
let Session { treeId: root } = session
let setFileType' val = T.write_ val fileType
let setLang' val = T.write_ val lang
......@@ -128,7 +131,7 @@ uploadFileViewCpt = here.component "uploadFileView" cpt
]
, R2.row
[ H.div { className: "col-6 flex-space-around" }
[ ListSelection.selection { selection } [] ]
[ ListSelection.selection { root, selection } [] ]
]
]
......
......@@ -25,7 +25,7 @@ import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), Settings
import Gargantext.Components.Forest.Tree.Node.Status (Status(..), hasStatus)
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT)
import Gargantext.Sessions (Session)
import Gargantext.Types (FrontendError, ID, Name, prettyNodeType)
import Gargantext.Types (ID, Name, prettyNodeType)
import Gargantext.Types as GT
import Gargantext.Utils.Glyphicon (glyphicon, glyphiconActive)
import Gargantext.Utils.Reactix as R2
......@@ -40,7 +40,7 @@ type CommonProps =
( dispatch :: Action -> Aff Unit
, session :: Session )
nodePopupView :: Record NodePopupProps -> R.Element
nodePopupView :: R2.Leaf NodePopupProps
nodePopupView p = R.createElement nodePopupCpt p []
nodePopupCpt :: R.Component NodePopupProps
nodePopupCpt = here.component "nodePopupView" cpt where
......
......@@ -6,7 +6,9 @@ import Data.Array as A
import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Gargantext.Components.App.Data (Boxes)
import Gargantext.Components.Forest.Tree.Node.Tools (formChoiceSafe)
import Gargantext.Sessions (Session(..), unSessions)
import Gargantext.Types (ListId)
import Gargantext.Utils.Reactix as R2
import Reactix as R
......@@ -30,18 +32,19 @@ instance Read Selection where
read _ = Nothing
type Props =
( selection :: T.Box Selection )
( root :: Int
, selection :: T.Box Selection )
selection :: R2.Component Props
selection = R.createElement selectionCpt
selectionCpt :: R.Component Props
selectionCpt = here.component "selection" cpt where
cpt { selection } _ = do
cpt { root, selection } _ = do
pure $ H.div {}
[ formChoiceSafe [ MyListsFirst
, OtherListsFirst
, SelectedLists [] ] MyListsFirst setSelection show
, selectedIds { selection } []
, selectedIds { root, selection } []
]
where
setSelection val = T.write_ val selection
......@@ -50,26 +53,27 @@ selectedIds :: R2.Component Props
selectedIds = R.createElement selectedIdsCpt
selectedIdsCpt :: R.Component Props
selectedIdsCpt = here.component "selectedIds" cpt where
cpt { selection } _ = do
cpt { root, selection } _ = do
selection' <- T.useLive T.unequal selection
pure $ case selection' of
SelectedLists ids -> H.div {} [ idsSelector { ids, selection } [] ]
SelectedLists ids -> H.div {} [ idsSelector { ids, root, selection } [] ]
_ -> H.div {} []
type IdsSelectorProps =
( ids :: Array ListId
, root :: Int
, selection :: T.Box Selection )
idsSelector :: R2.Component IdsSelectorProps
idsSelector = R.createElement idsSelectorCpt
idsSelectorCpt :: R.Component IdsSelectorProps
idsSelectorCpt = here.component "idsSelector" cpt where
cpt { ids, selection } _ = do
cpt { ids, root, selection } _ = do
R.useEffect' $ do
here.log2 "[idsSelector] ids" ids
pure $ H.div {} $ map checkbox [1, 2, 3, 4]
pure $ H.div {} [ listTree { ids, root, selection } [] ] -- $ map checkbox [1, 2, 3, 4]
where
checkbox val = H.div {}
[ H.input { className: "form-check-input"
......@@ -91,5 +95,6 @@ listTree :: R2.Component IdsSelectorProps
listTree = R.createElement listTreeCpt
listTreeCpt :: R.Component IdsSelectorProps
listTreeCpt = here.component "listTree" cpt where
cpt { ids, selection } _ = do
pure $ H.div {} []
cpt { ids, root, selection } _ = do
pure $ H.div {} [ H.text $ show root ]
......@@ -24,7 +24,7 @@ import Gargantext.Prelude (class Eq, class Show, Unit, bind, discard, pure, show
import Gargantext.Routes (SessionRoute(Children, NodeAPI))
import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, put, sessionId)
import Gargantext.Types (AffETableResult, NodeType(..))
import Gargantext.Types (AffETableResult, NodeType(..), ID)
import Gargantext.Utils.Crypto as Crypto
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
......@@ -38,7 +38,7 @@ here = R2.here "Gargantext.Components.Nodes.Corpus"
type Props =
( boxes :: Boxes
, nodeId :: Int
, nodeId :: ID
, session :: Session )
corpusLayout :: R2.Leaf Props
......@@ -53,7 +53,7 @@ corpusLayoutCpt = here.component "corpusLayout" cpt where
type KeyProps =
( boxes :: Boxes
, key :: String
, nodeId :: Int
, nodeId :: ID
, session :: Session
)
......@@ -88,11 +88,11 @@ corpusLayoutMainCpt = here.component "corpusLayoutMain" cpt
H.hr {}
,
FV.folderView
{ nodeId
, session
, backFolder: true
, boxes
}
{ backFolder: true
, boxes
, nodeId
, session
}
]
-----------------------------------
......
......@@ -183,7 +183,10 @@ tutorialCpt = here.component "tutorial" cpt where
sessionToFolder session@(Session {treeId, username, backend: (Backend {name})}) =
H.span { className: "folder" } [
H.div { className: "d-flex justify-content-center" } [ H.text (username <> "@" <> name) ]
, H.div {} [ FV.folderView { backFolder: false, boxes, nodeId: treeId, session } ] ]
, H.div {} [ FV.folderView { backFolder: false
, boxes
, nodeId: treeId
, session } ] ]
startTutos :: Array Tuto
startTutos =
......
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