Commit 69f83025 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] organize funs (WIP)

parent 1c082d54
......@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree where
import DOM.Simple.Console (log, log2)
import Data.Array as A
import Data.Maybe (Maybe)
import Data.Maybe (Maybe(..))
import Data.Set as Set
import Data.Tuple (Tuple(..), fst, snd)
import Data.Tuple.Nested ((/\))
......@@ -12,7 +12,6 @@ import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node (nodeMainSpan)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (AddNodeValue(..), addNode)
import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (getNodeTree)
import Gargantext.Components.Forest.Tree.Node.Action.Delete (deleteNode)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (RenameValue(..), rename)
import Gargantext.Components.Forest.Tree.Node.Action.Share (ShareValue(..), share)
......@@ -24,8 +23,10 @@ import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>))
import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (OpenNodes, Session, mkNodeId)
import Gargantext.Sessions (OpenNodes, Session, mkNodeId, get)
import Gargantext.Types (ID, Reload)
import Gargantext.Types as GT
import Gargantext.Routes as GR
import Reactix as R
import Reactix.DOM.HTML as H
import Record as Record
......@@ -95,6 +96,13 @@ treeLoadView p = R.createElement treeLoadViewCpt p []
}
useLoader { root, counter: fst reload } fetch paint
--------------
getNodeTree :: Session -> GT.ID -> Aff FTree
getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
--------------
type TreeViewProps = ( asyncTasks :: R.State GAT.Storage
, tree :: FTree
, tasks :: Record Tasks
......
......@@ -19,7 +19,6 @@ type UpdateNodeProps =
)
-}
data Action = AddNode String GT.NodeType
| DeleteNode
| RenameNode String
......@@ -30,7 +29,6 @@ data Action = AddNode String GT.NodeType
| DownloadNode
| RefreshTree
instance showShow :: Show Action where
show (AddNode _ _ )= "AddNode"
show DeleteNode = "DeleteNode"
......
......@@ -19,17 +19,11 @@ import Reactix.DOM.HTML as H
------------------------------------------------------------------------
getNodeTree :: Session -> GT.ID -> Aff FTree
getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
------------------------------------------------------------------------
type SubTreeParamsProps =
( subTreeParams :: SubTreeParams
| Props
)
copyFromCorpusView :: Record SubTreeParamsProps -> R.Element
copyFromCorpusView props = R.createElement copyFromCorpusViewCpt props []
......@@ -55,8 +49,17 @@ copyFromCorpusViewCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusView" cpt
, subTreeParams
}
------------------------------------------------------------------------
loadSubTree :: Array GT.NodeType -> Session -> Aff FTree
loadSubTree nodetypes session = getSubTree session treeId nodetypes
where
Session { treeId } = session
getSubTree :: Session -> Int -> Array GT.NodeType -> Aff FTree
getSubTree session treeId showtypes = get session $ GR.NodeAPI GT.Tree (Just treeId) nodeTypes
where
nodeTypes = A.foldl (\a b -> a <> "type=" <> show b <> "&") "?" showtypes
------------------------------------------------------------------------
type CorpusTreeProps =
( tree :: FTree
| SubTreeParamsProps
......@@ -91,10 +94,15 @@ copyFromCorpusTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusTreeVi
)
-- ]
where
SubTreeParams { valitypes } = subTreeParams
children = map (\c -> copyFromCorpusTreeView (p { tree = c })) ary
validNodeType = (A.elem nodeType valitypes) && (id /= sourceId)
clickable = if validNodeType then "clickable" else ""
onClick _ = case validNodeType of
false -> pure unit
true -> do
......@@ -102,14 +110,4 @@ copyFromCorpusTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.copyFromCorpusTreeVi
log2 "[copyFromCorpusTreeViewCpt] issue copy from" sourceId
--------------------------------------------------------------------------------------------
loadSubTree :: Array GT.NodeType -> Session -> Aff FTree
loadSubTree nodetypes session = getSubTree session treeId nodetypes
where
Session { treeId } = session
getSubTree :: Session -> Int -> Array GT.NodeType -> Aff FTree
getSubTree session treeId showtypes = get session $ GR.NodeAPI GT.Tree (Just treeId) nodeTypes
where
nodeTypes = A.foldl (\a b -> a <> "type=" <> show b <> "&") "?" showtypes
......@@ -238,6 +238,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
cpt {action: Config , dispatch, id, nodeType, session} _ = do
pure $ fragmentPT $ "Config " <> show nodeType
-----------
cpt {action: Merge {subTreeParams}, dispatch, id, nodeType, session} _ = do
pure $ copyFromCorpusView {dispatch, id, nodeType, session, subTreeParams}
......@@ -246,6 +247,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
cpt {action: Link {subTreeParams}, dispatch, id, nodeType, session} _ = do
pure $ copyFromCorpusView {dispatch, id, nodeType, session, subTreeParams}
-----------
cpt {action : Share, dispatch, id, name } _ = do
isOpen <- R.useState' true
......
......@@ -15,7 +15,8 @@ if user has access to node then he can do all his related actions
-}
------------------------------------------------------------------------
------------------------------------------------------------------------
data Status a = IsBeta a | IsProd a
-- Beta Status
data Status a = TODO a | WIP a | OnTest a | Beta a
data NodeAction = Documentation NodeType
| SearchBox
......@@ -250,6 +251,8 @@ settingsBox _ =
, buttons : []
}
-- | SubTree Parameters
moveParameters = { subTreeParams : SubTreeParams
{ showtypes: [ FolderPrivate
, FolderShared
......@@ -267,15 +270,15 @@ moveParameters = { subTreeParams : SubTreeParams
}
linkParams = { subTreeParams : SubTreeParams
{ showtypes: [ FolderPrivate
, FolderShared
, Team
, FolderPublic
, Folder
, Annuaire
]
, valitypes: [ Annuaire
]
}
}
{ showtypes: [ FolderPrivate
, FolderShared
, Team
, FolderPublic
, Folder
, Annuaire
]
, valitypes: [ Annuaire
]
}
}
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