Commit f06b3219 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DESIGN|REFACT] move

parent 326ae617
...@@ -16,6 +16,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) ...@@ -16,6 +16,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Reactix as R import Reactix as R
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel) import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsProps, subTreeView) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsProps, subTreeView)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsProps, subTreeView, SubTreeOut(..))
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
......
module Gargantext.Components.Forest.Tree.Node.Action.Move module Gargantext.Components.Forest.Tree.Node.Action.Move
where where
import Data.Argonaut as Argonaut
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Generic.Rep (class Generic)
import Gargantext.Prelude import Gargantext.Prelude
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Types as GT import Data.Tuple.Nested ((/\))
import Gargantext.Sessions (Session, put_) import Gargantext.Sessions (Session, put_)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson, genericEnumDecodeJson, genericEnumEncodeJson)
import Data.Generic.Rep.Show (genericShow)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Reactix as R import Reactix as R
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel) import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsProps, subTreeView) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeParamsProps, subTreeView, SubTreeOut(..))
import Gargantext.Types as GT
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
-- TODO moveNodeReq
moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Array GT.ID) moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Array GT.ID)
moveNodeReq session fromId toId = moveNodeReq session fromId toId =
put_ session $ NodeAPI GT.Node (Just fromId) ("move/" <> show toId) put_ session $ NodeAPI GT.Node (Just fromId) ("move/" <> show toId)
moveNode :: Record SubTreeParamsProps -> R.Hooks R.Element moveNode :: Record SubTreeParamsProps -> R.Hooks R.Element
moveNode p = do moveNode p@{subTreeOut, dispatch} = pure $ panel [subTreeView p] button
pure $ subTreeView p where
( subTreeOutParams /\ _ ) = subTreeOut
button = case subTreeOutParams of
Nothing -> H.div {} []
Just sbto -> submitButton (MoveNode inId outId) dispatch
where
(SubTreeOut { in:inId, out:outId}) = sbto
...@@ -27,7 +27,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Merge (mergeNode) ...@@ -27,7 +27,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Merge (mergeNode)
import Gargantext.Components.Forest.Tree.Node.Box.Types (NodePopupProps, NodePopupS) import Gargantext.Components.Forest.Tree.Node.Box.Types (NodePopupProps, NodePopupS)
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox) import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT) import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeOut) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (SubTreeOut)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (Name, ID) import Gargantext.Types (Name, ID)
import Gargantext.Types as GT import Gargantext.Types as GT
...@@ -249,6 +249,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt ...@@ -249,6 +249,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
pure $ fragmentPT $ "Config " <> show nodeType pure $ fragmentPT $ "Config " <> show nodeType
----------- -----------
-- Functions using SubTree
cpt {action: Merge {subTreeParams}, dispatch, id, nodeType, session} _ = do cpt {action: Merge {subTreeParams}, dispatch, id, nodeType, session} _ = do
subTreeOut :: R.State (Maybe SubTreeOut) <- R.useState' Nothing subTreeOut :: R.State (Maybe SubTreeOut) <- R.useState' Nothing
mergeNode {dispatch, id, nodeType, session, subTreeParams, subTreeOut} mergeNode {dispatch, id, nodeType, session, subTreeParams, subTreeOut}
...@@ -265,12 +266,13 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt ...@@ -265,12 +266,13 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
cpt {action : Share, dispatch, id, name } _ = do cpt {action : Share, dispatch, id, name } _ = do
isOpen <- R.useState' true isOpen <- R.useState' true
pure $ H.div {} [ textInputBox { boxAction: Share.shareAction pure $ H.div {} [ textInputBox { boxAction: Share.shareAction
, boxName: "Share" , boxName: "Share"
, dispatch , dispatch
, id , id
, text: "username" , text: "username"
, isOpen , isOpen
} ] }
]
cpt props@{action: SearchBox, id, session, dispatch, nodePopup} _ = cpt props@{action: SearchBox, id, session, dispatch, nodePopup} _ =
actionSearch session (Just id) dispatch nodePopup actionSearch session (Just id) dispatch nodePopup
......
...@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Tools.SubTree where ...@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Tools.SubTree where
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Data.Array as A import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (mkEffectFn1)
...@@ -11,7 +12,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Props, Action(..)) ...@@ -11,7 +12,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Props, Action(..))
import Gargantext.Components.Forest.Tree.Node.Settings (SubTreeParams(..)) import Gargantext.Components.Forest.Tree.Node.Settings (SubTreeParams(..))
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..)) import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..))
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (discard, map, pure, show, unit, ($), (&&), (/=), (<>), class Eq) import Gargantext.Prelude (discard, map, pure, show, unit, ($), (&&), (/=), (<>), class Eq, const)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Sessions (Session(..), get) import Gargantext.Sessions (Session(..), get)
import Gargantext.Types as GT import Gargantext.Types as GT
...@@ -98,6 +99,7 @@ subTreeTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.subTreeTreeViewCpt" cpt ...@@ -98,6 +99,7 @@ subTreeTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.subTreeTreeViewCpt" cpt
) ary ) ary
, subTreeParams , subTreeParams
, dispatch , dispatch
, subTreeOut
} _ = do } _ = do
pure $ {- H.div {} [ H.h5 { className: GT.fldr nodeType true} [] pure $ {- H.div {} [ H.h5 { className: GT.fldr nodeType true} []
, -} H.div { className: "node" } , -} H.div { className: "node" }
...@@ -117,14 +119,10 @@ subTreeTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.subTreeTreeViewCpt" cpt ...@@ -117,14 +119,10 @@ subTreeTreeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.subTreeTreeViewCpt" cpt
validNodeType = (A.elem nodeType valitypes) && (id /= sourceId) validNodeType = (A.elem nodeType valitypes) && (id /= sourceId)
clickable = if validNodeType then "clickable" else "" clickable = if validNodeType then "clickable" else ""
sbto@( subTreeOutParams /\ setSubTreeOut) = subTreeOut
onClick _ = mkEffectFn1 onClick _ = mkEffectFn1 $ \_ -> case validNodeType of
$ \_ -> case validNodeType of false -> setSubTreeOut (const Nothing)
false -> launchAff $ dispatch NoAction true -> setSubTreeOut (const $ Just $ SubTreeOut { in: id, out:sourceId})
true -> do
log2 "[subTreeTreeViewCpt] from" id
log2 "[subTreeTreeViewCpt] to" sourceId
launchAff $ dispatch (MoveNode id sourceId)
-------------------------------------------------------------------------------------------- --------------------------------------------------------------------------------------------
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