Commit 61edeb56 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-merge' into dev

parents 8d164617 f44f81c0
......@@ -455,11 +455,13 @@ performAction (UploadArbitraryFile mName blob) { asyncTasks: (_ /\ dispatch)
performAction DownloadNode _ = do
liftEffect $ log "[performAction] DownloadNode"
-------
performAction (MoveNode {params}) p@{session} =
performAction (MoveNode {params}) p@{ openNodes: (_ /\ setOpenNodes)
, session } =
case params of
Nothing -> performAction NoAction p
Just (SubTreeOut {in:in',out}) -> do
void $ moveNodeReq session in' out
liftEffect $ setOpenNodes (Set.insert (mkNodeId session out))
performAction RefreshTree p
performAction (MergeNode {params}) p@{session} =
......
......@@ -115,7 +115,7 @@ nodeMainSpan = R.createElement nodeMainSpanCpt
, name: name' props
, nodeType
, session
}
} []
, fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType }
, H.div {} (map (\t -> asyncProgressBar { asyncTask: t
......
......@@ -2,6 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action where
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Gargantext.Prelude (class Show, Unit)
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
......
......@@ -6,15 +6,16 @@ import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools (submitButton, panel)
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree (subTreeView, SubTreeParamsIn)
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, put_)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Move"
moveNodeReq :: Session -> GT.ID -> GT.ID -> Aff (Array GT.ID)
......@@ -23,11 +24,11 @@ moveNodeReq session fromId toId =
moveNode :: Record SubTreeParamsIn -> R.Element
moveNode p = R.createElement moveNodeCpt p []
moveNodeCpt :: R.Component SubTreeParamsIn
moveNodeCpt = R.hooksComponentWithModule thisModule "moveNode" cpt
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})
let button = case valAction of
......
......@@ -14,8 +14,8 @@ import Gargantext.Components.Lang (Lang)
import Gargantext.Prelude (Unit, pure, ($))
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar"
type Props = ( langs :: Array Lang
......
......@@ -5,7 +5,6 @@ import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Nullable (null)
import Data.Newtype (over)
import Data.Set as Set
import Data.String (length)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (launchAff_)
......@@ -24,6 +23,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField"
defaultSearch :: Search
......@@ -78,18 +78,24 @@ searchField p = R.createElement searchFieldComponent p []
, if isCNRS s.datafield
then componentCNRS search
else H.div {} []
, H.div {} [ searchIframes { iframeRef, search } ]
, if needsLang s.datafield
then langNav search props.langs
else H.div {} []
, H.div {} [ searchIframes { iframeRef, search } ]
]
]
let button = submitButton {onSearch, search, session: props.session}
pure $ panel params button
pure $ H.div { className: "search-field" }
[ H.div { className: "row" }
[ H.div { className: "col-12" } params ]
, H.div { className: "row" }
[ H.div { className: "col-12" } [ button ] ]
]
--pure $ panel params button
componentIMT (search /\ setSearch) =
......@@ -252,27 +258,6 @@ dataFieldNav ({datafield} /\ setSearch) datafields =
isActive = show (Just df') == show datafield
------------------------------------------------------------------------
{-
databaseNav :: R.State Search
-> Array Database
-> R.Element
databaseNav ({datafield} /\ setSearch) dbs =
R.fragment [ H.div {className: "text-primary center"} [H.text "with DataField"]
, H.div { className: "nav nav-tabs"} (liItem <$> dbs)
, H.div {className:"center"} [ H.text $ maybe "" doc db ]
]
where
db = case datafield of
(Just (External (Just x))) -> Just x
_ -> Nothing
liItem :: Database -> R.Element
liItem df' =
H.div { className : "nav-item nav-link" <> if (Just $ External $ Just df') == datafield then " active" else ""
, on: { click: \_ -> setSearch $ _ { datafield = Just $ External $ Just df' } }
} [ H.text (show df') ]
-}
type DatabaseInputProps = (
databases :: Array Database
......@@ -352,10 +337,10 @@ type SearchInputProps =
)
searchInput :: Record SearchInputProps -> R.Element
searchInput p = R.createElement searchInputComponent p []
searchInput p = R.createElement searchInputCpt p []
where
searchInputComponent :: R.Component SearchInputProps
searchInputComponent = R.hooksComponentWithModule thisModule "searchInput" cpt
searchInputCpt :: R.Component SearchInputProps
searchInputCpt = R.hooksComponentWithModule thisModule "searchInput" cpt
cpt {search: (search@{ term } /\ setSearch)} _ = do
valueRef <- R.useRef term
......
......@@ -20,8 +20,8 @@ import Gargantext.Sessions (Session, post)
import Gargantext.Types (ID)
import Gargantext.Types as GT
import Gargantext.Utils.Argonaut (genericSumDecodeJson, genericSumEncodeJson)
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Action.Share"
------------------------------------------------------------------------
......@@ -34,7 +34,7 @@ shareAction username = Action.ShareTeam username
------------------------------------------------------------------------
textInputBox :: Record Tools.TextInputBoxProps -> R.Element
textInputBox = Tools.textInputBox
textInputBox p = Tools.textInputBox p []
------------------------------------------------------------------------
data ShareNodeParams = ShareTeamParams { username :: String }
......
......@@ -100,7 +100,7 @@ nodePopupView p = R.createElement nodePopupCpt p []
, id
, text: name
, isOpen: renameIsOpen
}
} []
else
H.span { className: "text-primary center" } [H.text p.name]
]
......@@ -291,18 +291,18 @@ panelAction p = R.createElement panelActionCpt p []
, id
, text: "username"
, isOpen
}
} []
] $ H.div {} []
cpt {action : AddingContact, dispatch, id, name } _ = do
isOpen <- R.useState' true
pure $ Contact.textInputBox { id
, dispatch
, isOpen
, boxName:"addContact"
, params : {firstname:"First Name", lastname: "Last Name"}
, boxAction: \p -> AddContact p
}
, dispatch
, isOpen
, boxName:"addContact"
, params : {firstname:"First Name", lastname: "Last Name"}
, boxAction: \p -> AddContact p
}
......
......@@ -35,20 +35,20 @@ type Footer = R.Element
panel :: Body -> Footer -> R.Element
panel bodies submit =
R.fragment [ panelBody bodies, footer submit ]
R.fragment [ panelBody, footer ]
where
panelBody bs =
panelBody =
H.div { className: "card-body" }
[ H.div { className: "row" }
[ H.div { className: "col-12" } bs
[ H.div { className: "col-12" } bodies
-- TODO add type for text or form here
-- [ H.form {className: "form-horizontal"} bs ]
-- [ H.form {className: "form-horizontal"} bodies ]
]
]
footer sb =
footer =
H.div {className: "card-footer"}
[ H.div { className: "row" }
[ H.div { className: "mx-auto"} [ sb ]
[ H.div { className: "mx-auto"} [ submit ]
]
]
......@@ -64,22 +64,23 @@ type TextInputBoxProps =
, boxAction :: String -> Action
)
textInputBox :: Record TextInputBoxProps -> R.Element
textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R.createElement el p []
textInputBox :: R2.Component TextInputBoxProps
textInputBox props@{ boxName } = R.createElement el props
where
el :: R.Component TextInputBoxProps
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
pure $ H.div {className: "from-group row"}
pure $ H.div { className: "from-group row" }
[ textInput renameNodeNameRef
, submitBtn renameNodeNameRef
, cancelBtn
]
where
textInput renameNodeNameRef =
H.div {className: "col-8"}
H.div { className: "col-8" }
[ inputWithEnter {
onEnter: submit renameNodeNameRef
, onValueChanged: R.setRef renameNodeNameRef
......@@ -90,23 +91,15 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R
, placeholder: (boxName <> " Node")
, type: "text"
}
-- [ H.input { type: "text"
-- , placeholder: (boxName <> " Node")
-- , defaultValue: text
-- , className: "form-control"
-- , on: { input: setRenameNodeName
-- <<< const
-- <<< R.unsafeEventValue }
-- }
]
]
submitBtn renameNodeNameRef =
H.a {className: "col-2 " <> glyphicon "floppy-o"
H.a { className: "col-2 " <> glyphicon "floppy-o"
, type: "button"
, on: { click: submit renameNodeNameRef }
, title: "Submit"
} []
cancelBtn =
H.a {className: "text-danger col-2 " <> glyphicon "times"
H.a { className: "text-danger col-2 " <> glyphicon "times"
, type: "button"
, on: { click: \_ -> setIsOpen $ const false }
, title: "Cancel"
......@@ -114,10 +107,7 @@ textInputBox p@{ boxName, boxAction, dispatch, isOpen: (true /\ setIsOpen) } = R
submit renameNodeNameRef _ = do
setIsOpen $ const false
launchAff_ $ dispatch ( boxAction $ R.readRef renameNodeNameRef )
textInputBox p@{ boxName, isOpen: (false /\ _) } = R.createElement el p []
where
el = R.hooksComponentWithModule thisModule (boxName <> "Box") cpt
cpt {text} _ = pure $ H.div {} []
cpt { isOpen: (false /\ _) } _ = pure $ H.div {} []
-- | END Rename Box
......@@ -300,12 +290,12 @@ type NodeLinkProps = (
, handed :: GT.Handed
)
nodeLink :: Record NodeLinkProps -> R.Element
nodeLink p = R.createElement nodeLinkCpt p []
nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
nodeLink :: R2.Component NodeLinkProps
nodeLink = R.createElement nodeLinkCpt
where
nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
cpt { folderOpen: (_ /\ setFolderOpen)
, frontends
, handed
......@@ -358,10 +348,10 @@ type NodeTextProps =
nodeText :: Record NodeTextProps -> R.Element
nodeText p = R.createElement nodeTextCpt p []
nodeTextCpt :: R.Component NodeTextProps
nodeTextCpt = R.hooksComponentWithModule thisModule "nodeText" cpt
where
nodeTextCpt :: R.Component NodeTextProps
nodeTextCpt = R.hooksComponentWithModule thisModule "nodeText" cpt
cpt { isSelected: true, name } _ = do
pure $ H.u {} [
H.b {} [
......
......@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree.Node.Tools.SubTree where
import Data.Array as A
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect.Uncurried (mkEffectFn1)
import Effect.Aff (Aff)
import React.SyntheticEvent as E
import Reactix as R
......@@ -19,8 +18,8 @@ import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR
import Gargantext.Sessions (Session(..), get)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Tools.SubTree"
type SubTreeParamsIn =
......@@ -37,10 +36,10 @@ type SubTreeParamsProps =
subTreeView :: Record SubTreeParamsProps -> R.Element
subTreeView props = R.createElement subTreeViewCpt props []
subTreeViewCpt :: R.Component SubTreeParamsProps
subTreeViewCpt = R.hooksComponentWithModule thisModule "subTreeView" cpt
where
subTreeViewCpt :: R.Component SubTreeParamsProps
subTreeViewCpt = R.hooksComponentWithModule thisModule "subTreeView" cpt
cpt params@{ action
, dispatch
, 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