Commit 7f97bed3 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[bootstrap v4] open parent when moving node

parent 25507fe9
...@@ -455,11 +455,13 @@ performAction (UploadArbitraryFile mName blob) { asyncTasks: (_ /\ dispatch) ...@@ -455,11 +455,13 @@ performAction (UploadArbitraryFile mName blob) { asyncTasks: (_ /\ dispatch)
performAction DownloadNode _ = do performAction DownloadNode _ = do
liftEffect $ log "[performAction] DownloadNode" liftEffect $ log "[performAction] DownloadNode"
------- -------
performAction (MoveNode {params}) p@{session} = performAction (MoveNode {params}) p@{ openNodes: (_ /\ setOpenNodes)
, session } =
case params of case params of
Nothing -> performAction NoAction p Nothing -> performAction NoAction p
Just (SubTreeOut {in:in',out}) -> do Just (SubTreeOut {in:in',out}) -> do
void $ moveNodeReq session in' out void $ moveNodeReq session in' out
liftEffect $ setOpenNodes (Set.insert (mkNodeId session out))
performAction RefreshTree p performAction RefreshTree p
performAction (MergeNode {params}) p@{session} = performAction (MergeNode {params}) p@{session} =
......
...@@ -115,7 +115,7 @@ nodeMainSpan = R.createElement nodeMainSpanCpt ...@@ -115,7 +115,7 @@ nodeMainSpan = R.createElement nodeMainSpanCpt
, name: name' props , name: name' props
, nodeType , nodeType
, session , session
} } []
, fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType } , fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType }
, H.div {} (map (\t -> asyncProgressBar { asyncTask: t , H.div {} (map (\t -> asyncProgressBar { asyncTask: t
......
...@@ -2,6 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action where ...@@ -2,6 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action where
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Prelude (class Show, Unit) import Gargantext.Prelude (class Show, Unit)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types as GT import Gargantext.Types as GT
......
...@@ -6,15 +6,16 @@ import Effect.Aff (Aff) ...@@ -6,15 +6,16 @@ import Effect.Aff (Aff)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
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 (subTreeView, SubTreeParamsIn) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, put_) import Gargantext.Sessions (Session, put_)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Move" thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Move"
moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Array GT.ID) moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Array GT.ID)
...@@ -23,11 +24,11 @@ moveNodeReq session fromId toId = ...@@ -23,11 +24,11 @@ moveNodeReq session fromId toId =
moveNode :: Record SubTreeParamsIn -> R.Element moveNode :: Record SubTreeParamsIn -> R.Element
moveNode p = R.createElement moveNodeCpt p [] moveNode p = R.createElement moveNodeCpt p []
moveNodeCpt :: R.Component SubTreeParamsIn
moveNodeCpt = R.hooksComponentWithModule thisModule "moveNode" cpt
where where
cpt p@{dispatch, subTreeParams, id, nodeType, session, handed} _ = do moveNodeCpt :: R.Component SubTreeParamsIn
moveNodeCpt = R.hooksComponentWithModule thisModule "moveNode" cpt
cpt { dispatch, handed, id, nodeType, session, subTreeParams } _ = do
action@(valAction /\ setAction) :: R.State Action <- R.useState' (MoveNode {params: Nothing}) action@(valAction /\ setAction) :: R.State Action <- R.useState' (MoveNode {params: Nothing})
let button = case valAction of let button = case valAction of
......
...@@ -20,8 +20,8 @@ import Gargantext.Sessions (Session, post) ...@@ -20,8 +20,8 @@ import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID) import Gargantext.Types (ID)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson) import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson)
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Share" thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Share"
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -34,7 +34,7 @@ shareAction username = Action.ShareTeam username ...@@ -34,7 +34,7 @@ shareAction username = Action.ShareTeam username
------------------------------------------------------------------------ ------------------------------------------------------------------------
textInputBox :: Record Tools.TextInputBoxProps -> R.Element textInputBox :: Record Tools.TextInputBoxProps -> R.Element
textInputBox = Tools.textInputBox textInputBox p = Tools.textInputBox p []
------------------------------------------------------------------------ ------------------------------------------------------------------------
data ShareNodeParams = ShareTeamParams { username :: String } data ShareNodeParams = ShareTeamParams { username :: String }
......
...@@ -100,7 +100,7 @@ nodePopupView p = R.createElement nodePopupCpt p [] ...@@ -100,7 +100,7 @@ nodePopupView p = R.createElement nodePopupCpt p []
, id , id
, text: name , text: name
, isOpen: renameIsOpen , isOpen: renameIsOpen
} } []
else else
H.span { className: "text-primary center" } [H.text p.name] H.span { className: "text-primary center" } [H.text p.name]
] ]
...@@ -291,7 +291,7 @@ panelAction p = R.createElement panelActionCpt p [] ...@@ -291,7 +291,7 @@ panelAction p = R.createElement panelActionCpt p []
, id , id
, text: "username" , text: "username"
, isOpen , isOpen
} } []
] $ H.div {} [] ] $ H.div {} []
cpt {action : AddingContact, dispatch, id, name } _ = do cpt {action : AddingContact, dispatch, id, name } _ = do
......
...@@ -64,22 +64,23 @@ type TextInputBoxProps = ...@@ -64,22 +64,23 @@ type TextInputBoxProps =
, boxAction :: String -> Action , boxAction :: String -> Action
) )
textInputBox :: Record TextInputBoxProps -> R.Element textInputBox :: R2.Component TextInputBoxProps
textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R.createElement el p [] textInputBox props@{ boxName } = R.createElement el props
where where
el :: R.Component TextInputBoxProps
el = R.hooksComponentWithModule thisModule (boxName <> "Box") cpt el = R.hooksComponentWithModule thisModule (boxName <> "Box") cpt
cpt {id, text} _ = do cpt p@{ boxAction, dispatch, id, isOpen: (true /\ setIsOpen), text } _ = do
renameNodeNameRef <- R.useRef text renameNodeNameRef <- R.useRef text
pure $ H.div {className: "from-group row"} pure $ H.div { className: "from-group row" }
[ textInput renameNodeNameRef [ textInput renameNodeNameRef
, submitBtn renameNodeNameRef , submitBtn renameNodeNameRef
, cancelBtn , cancelBtn
] ]
where where
textInput renameNodeNameRef = textInput renameNodeNameRef =
H.div {className: "col-8"} H.div { className: "col-8" }
[ inputWithEnter { [ inputWithEnter {
onEnter: submit renameNodeNameRef onEnter: submit renameNodeNameRef
, onValueChanged: R.setRef renameNodeNameRef , onValueChanged: R.setRef renameNodeNameRef
...@@ -90,23 +91,15 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R ...@@ -90,23 +91,15 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R
, placeholder: (boxName <> " Node") , placeholder: (boxName <> " Node")
, type: "text" , type: "text"
} }
-- [ H.input { type: "text"
-- , placeholder: (boxName <> " Node")
-- , defaultValue: text
-- , className: "form-control"
-- , on: { input: setRenameNodeName
-- <<< const
-- <<< R.unsafeEventValue }
-- }
] ]
submitBtn renameNodeNameRef = submitBtn renameNodeNameRef =
H.a {className: "col-2 " <> glyphicon "floppy-o" H.a { className: "col-2 " <> glyphicon "floppy-o"
, type: "button" , type: "button"
, on: { click: submit renameNodeNameRef } , on: { click: submit renameNodeNameRef }
, title: "Submit" , title: "Submit"
} [] } []
cancelBtn = cancelBtn =
H.a {className: "text-danger col-2 " <> glyphicon "times" H.a { className: "text-danger col-2 " <> glyphicon "times"
, type: "button" , type: "button"
, on: { click: \_ -> setIsOpen $ const false } , on: { click: \_ -> setIsOpen $ const false }
, title: "Cancel" , title: "Cancel"
...@@ -114,10 +107,7 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R ...@@ -114,10 +107,7 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R
submit renameNodeNameRef _ = do submit renameNodeNameRef _ = do
setIsOpen $ const false setIsOpen $ const false
launchAff_ $ dispatch ( boxAction $ R.readRef renameNodeNameRef ) launchAff_ $ dispatch ( boxAction $ R.readRef renameNodeNameRef )
textInputBox p@{ boxName, isOpen: (false /\ _) } = R.createElement el p [] cpt { isOpen: (false /\ _) } _ = pure $ H.div {} []
where
el = R.hooksComponentWithModule thisModule (boxName <> "Box") cpt
cpt {text} _ = pure $ H.div {} []
-- | END Rename Box -- | END Rename Box
...@@ -300,12 +290,12 @@ type NodeLinkProps = ( ...@@ -300,12 +290,12 @@ type NodeLinkProps = (
, handed :: GT.Handed , handed :: GT.Handed
) )
nodeLink :: Record NodeLinkProps -> R.Element nodeLink :: R2.Component NodeLinkProps
nodeLink p = R.createElement nodeLinkCpt p [] nodeLink = R.createElement nodeLinkCpt
nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
where where
nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
cpt { folderOpen: (_ /\ setFolderOpen) cpt { folderOpen: (_ /\ setFolderOpen)
, frontends , frontends
, handed , handed
...@@ -358,10 +348,10 @@ type NodeTextProps = ...@@ -358,10 +348,10 @@ type NodeTextProps =
nodeText :: Record NodeTextProps -> R.Element nodeText :: Record NodeTextProps -> R.Element
nodeText p = R.createElement nodeTextCpt p [] nodeText p = R.createElement nodeTextCpt p []
nodeTextCpt :: R.Component NodeTextProps
nodeTextCpt = R.hooksComponentWithModule thisModule "nodeText" cpt
where where
nodeTextCpt :: R.Component NodeTextProps
nodeTextCpt = R.hooksComponentWithModule thisModule "nodeText" cpt
cpt { isSelected: true, name } _ = do cpt { isSelected: true, name } _ = do
pure $ H.u {} [ pure $ H.u {} [
H.b {} [ H.b {} [
......
...@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree.Node.Tools.SubTree where ...@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree.Node.Tools.SubTree where
import Data.Array as A import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Uncurried (mkEffectFn1)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import React.SyntheticEvent as E import React.SyntheticEvent as E
import Reactix as R import Reactix as R
...@@ -19,8 +18,8 @@ import Gargantext.Hooks.Loader (useLoader) ...@@ -19,8 +18,8 @@ import Gargantext.Hooks.Loader (useLoader)
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
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Tools.SubTree" thisModule = "Gargantext.Components.Forest.Tree.Node.Tools.SubTree"
type SubTreeParamsIn = type SubTreeParamsIn =
...@@ -37,10 +36,10 @@ type SubTreeParamsProps = ...@@ -37,10 +36,10 @@ type SubTreeParamsProps =
subTreeView :: Record SubTreeParamsProps -> R.Element subTreeView :: Record SubTreeParamsProps -> R.Element
subTreeView props = R.createElement subTreeViewCpt props [] subTreeView props = R.createElement subTreeViewCpt props []
subTreeViewCpt :: R.Component SubTreeParamsProps
subTreeViewCpt = R.hooksComponentWithModule thisModule "subTreeView" cpt
where where
subTreeViewCpt :: R.Component SubTreeParamsProps
subTreeViewCpt = R.hooksComponentWithModule thisModule "subTreeView" cpt
cpt params@{ action cpt params@{ action
, dispatch , dispatch
, handed , handed
......
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