Commit 7b004cb5 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FOREST/TREE] Node refacto.

parent 235b9ba9
module Gargantext.Components.Forest.Action where
import Prelude hiding (div)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..), fromJust)
import Data.Newtype (class Newtype)
import Effect.Aff (Aff, launchAff, runAff)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Gargantext.Routes (AppRoute, SessionRoute(..))
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Gargantext.Sessions (Session, sessionId, get, put, post, postWwwUrlencoded, delete)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Generic.Rep.Eq (genericEq)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Prelude hiding (div)
-- file upload types
data Action = Submit String
......@@ -18,6 +18,8 @@ data Action = Submit String
| CreateSubmit String NodeType
| UploadFile FileType UploadFileContents
-----------------------------------------------------
-- UploadFile Action
data FileType = CSV | PresseRIS
derive instance genericFileType :: Generic FileType _
......@@ -44,10 +46,13 @@ type FileHash = String
type Name = String
type ID = Int
type Reload = Int
data NodePopup = CreatePopup | NodePopup
newtype UploadFileContents = UploadFileContents String
createNode :: Session -> ID -> CreateValue -> Aff ID
createNode session parentId = post session $ NodeAPI Node (Just parentId) ""
......@@ -117,4 +122,3 @@ instance decodeJsonFTree :: DecodeJson (NTree LNode) where
nodes' <- decodeJson nodes
pure $ NTree node' nodes'
module Gargantext.Components.Forest.Action.Add where
import Prelude hiding (div)
import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Array (filter, null)
......@@ -16,7 +14,18 @@ import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Gargantext.Components.Forest.NodeActions
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (AppRoute, SessionRoute(..))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, get, put, post, postWwwUrlencoded, delete)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Gargantext.Utils (id, glyphicon)
import Gargantext.Utils.Reactix as R2
import Partial.Unsafe (unsafePartial)
import Prelude hiding (div)
import React.SyntheticEvent as E
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -26,28 +35,21 @@ import Web.File.File (toBlob)
import Web.File.FileList (FileList, item)
import Web.File.FileReader.Aff (readAsText)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as Routes
import Gargantext.Routes (AppRoute, SessionRoute(..))
import Gargantext.Sessions (Session, sessionId, get, put, post, postWwwUrlencoded, delete)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Gargantext.Utils (id, glyphicon)
import Gargantext.Utils.Reactix as R2
import Gargantext.Components.Forest.NodeActions
import Gargantext.Components.Forest.Action
-- START Create Node
data NodePopup = CreatePopup | NodePopup
type CreateNodeProps =
( id :: ID
, name :: Name
, nodeType :: NodeType)
, nodeType :: NodeType
)
createNodeView :: (Action -> Aff Unit)
-> Record CreateNodeProps
-> R.State (Maybe NodePopup)
-> R.Element
createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
createNodeView d p@{nodeType} (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
where
el = R.hooksComponent "CreateNodeView" cpt
cpt {id, name} _ = do
......@@ -61,8 +63,10 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
]
]
where
SettingsBox {add:nodeTypes} = settingsBox nodeType
tooltipProps = { className: ""
, id: "add-node-tooltip"
, id: "create-node-tooltip"
, title: "Add new node"
, data: {toggle: "tooltip", placement: "right"}
}
......@@ -86,7 +90,7 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
[ H.div {className: "row"}
[ H.div {className: "col-md-12"}
[ H.form {className: "form-horizontal"}
[ H.div {className: "form-group"}
[ {- H.div {className: "form-group"}
[ H.input { type: "text"
, placeholder: "Node name"
, defaultValue: name
......@@ -94,11 +98,11 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
, onInput: mkEffectFn1 $ \e -> setNodeName $ const $ e .. "target" .. "value"
}
]
, H.div {className: "form-group"}
, -} H.div {className: "form-group"}
[ R2.select { className: "form-control"
, onChange: mkEffectFn1 $ \e -> setNodeType $ const $ readNodeType $ e .. "target" .. "value"
}
(map renderOption [FolderPublic, FolderShared, FolderPrivate])
(map renderOption nodeTypes)
]
]
]
......
module Gargantext.Components.Forest.Action.Rename where
import Prelude hiding (div)
import Data.Tuple.Nested ((/\))
import Reactix.DOM.HTML as H
import Reactix as R
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
import Prelude hiding (div)
import Reactix as R
import Reactix.DOM.HTML as H
-- START Rename Box
-- | START Rename Box
type RenameBoxProps =
( id :: ID
, name :: Name)
......
......@@ -19,75 +19,149 @@ filterWithRights (show action if user can only)
-}
nodeActions :: NodeType -> Array NodeAction
nodeActions NodeUser = [ Add [ FolderPrivate
data SettingsBox =
SettingsBox { show :: Boolean
, edit :: Boolean
, add :: Array NodeType
, buttons :: Array NodeAction
}
settingsBox :: NodeType -> SettingsBox
settingsBox NodeUser = SettingsBox { show : true
, edit : false
, add : [ FolderPrivate
, FolderShared
, FolderPublic
]
, buttons : [Documentation NodeUser
, Delete
]
}
settingsBox FolderPrivate = SettingsBox { show: true
, edit : false
, add : [ Folder
, Corpus
]
, buttons : [Documentation FolderPrivate, Delete]
}
nodeActions FolderPrivate = [ Add [Folder, Corpus]]
nodeActions FolderShared = [ Add [Folder, Corpus]]
nodeActions FolderPublic = [ Add [Folder, Corpus]]
settingsBox FolderShared = SettingsBox { show: true
, edit : false
, add : [ Folder
, Corpus
]
, buttons : [Documentation FolderShared, Delete]
}
nodeActions Folder = [ Add [Corpus], Rename, Delete]
settingsBox FolderPublic = SettingsBox { show: true
, edit : false
, add : [ Folder
, Corpus
]
, buttons : [Documentation FolderPublic, Delete]
}
nodeActions Corpus = [ Rename
, Search, Upload, Download
, Add [NodeList, Dashboard, Graph, Phylo]
, Share, Move , Clone
settingsBox Folder = SettingsBox { show : true
, edit : true
, add : [ Folder
, Corpus
]
, buttons : [Documentation Folder, Delete]
}
settingsBox Corpus = SettingsBox { show : true
, edit : true
, add : [ NodeList
, Dashboard
, Graph
, Phylo
]
, buttons : [ Documentation Corpus
, Search
, Upload
, Download
, Share
, Move
, Clone
, Delete
]
}
nodeActions Graph = [Add [Graph], Delete]
nodeActions Texts = [Download, Upload, Delete]
settingsBox Texts = SettingsBox { show : true
, edit : false
, add : []
, buttons : [ Documentation Texts
, Upload
, Download
]
}
nodeActions _ = []
settingsBox Graph = SettingsBox { show : true
, edit : false
, add : [Graph]
, buttons : [ Documentation Graph
, Upload
, Download
]
}
settingsBox NodeList = SettingsBox { show : true
, edit : false
, add : [NodeList]
, buttons : [ Documentation NodeList
, Upload
, Download
]
}
settingsBox Dashboard = SettingsBox { show : true
, edit : false
, add : []
, buttons : [ Documentation Dashboard
]
}
settingsBox _ = SettingsBox { show : false
, edit : false
, add : []
, buttons : []
}
------------------------------------------------------------------------
data NodeAction = Rename
| Documentation NodeType
| Add (Array NodeType)
------------------------------------------------------------------------
data NodeAction = Documentation NodeType
| Search
| Download | Upload | Refresh
| Move | Clone | Delete
| Share
data ButtonType = Edit | Click | Pop
data ButtonType = Click | Pop
instance eqButtonType :: Eq ButtonType where
eq Edit Edit = true
eq Click Click = true
eq Pop Pop = true
eq _ _ = false
buttonType :: NodeAction -> ButtonType
buttonType Rename = Edit
buttonType (Add _) = Pop
buttonType Search = Pop
buttonType _ = Click
data Buttons = Buttons { edit :: Array NodeAction
, click :: Array NodeAction
data Buttons = Buttons { click :: Array NodeAction
, pop :: Array NodeAction
}
buttons nt = Buttons {edit, click, pop}
{-
buttons nt = Buttons {click, pop}
where
edit = filter' Edit
click = filter' Click
pop = filter' Pop
filter' b = filter (\a -> buttonType a == b)
(nodeActions nt)
click = init
pop = rest
{init, rest} = span buttonType (nodeActions nt)
-}
---------------------------------------------------------
......@@ -28,7 +28,6 @@ import Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>))
import Reactix as R
import Reactix.DOM.HTML as H
------------------------------------------------------------------------
type Props = ( root :: ID
, mCurrentRoute :: Maybe AppRoute
......@@ -98,10 +97,12 @@ toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary)} /\ _)
]
childNodes :: Session -> Frontends
-> R.State Reload -> R.State Boolean
-> Maybe AppRoute -> Array FTree
childNodes :: Session
-> Frontends
-> R.State Reload
-> R.State Boolean
-> Maybe AppRoute
-> Array FTree
-> Array R.Element
childNodes _ _ _ _ _ [] = []
childNodes _ _ _ (false /\ _) _ _ = []
......@@ -116,8 +117,11 @@ childNodes session frontends reload (true /\ _) mCurrentRoute ary =
pure $ toHtml reload treeState session frontends mCurrentRoute
performAction :: Session -> R.State Int -> R.State Tree -> Action -> Aff Unit
performAction :: Session
-> R.State Int
-> R.State Tree
-> Action
-> Aff Unit
performAction session (_ /\ setReload) (s@{tree: NTree (LNode {id}) _} /\ setTree) DeleteNode = do
void $ deleteNode session id
liftEffect $ setReload (_ + 1)
......@@ -134,4 +138,3 @@ performAction session _ ({tree: NTree (LNode {id}) _} /\ _) (UploadFile fileType
hashes <- uploadFile session id fileType contents
liftEffect $ log2 "uploaded:" hashes
......@@ -53,19 +53,25 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false
pure $ H.span (dropProps droppedFile isDragOver)
pure $ H.span (dropProps droppedFile isDragOver) $
[ folderIcon folderOpen
, H.a { href: (url frontends (NodePath (sessionId session) nodeType (Just id)))
, style: {marginLeft: "22px"}
}
[ nodeText {isSelected: (mCorpusId mCurrentRoute) == (Just id), name:name'} ]
, popOverIcon popupOpen
, nodePopupView d {id, name, nodeType} popupOpen
, createNodeView d {id, name, nodeType} popupOpen
, fileTypeView d {id , nodeType} droppedFile isDragOver
[ nodeText { isSelected: (mCorpusId mCurrentRoute) == (Just id)
, name: name'} ]
, if showBox then popOverIcon popupOpen else H.div {} []
, if showBox then nodePopupView d {id, name:name', nodeType} popupOpen else H.div {} []
, addButton popupOpen
, fileTypeView d {id, nodeType} droppedFile isDragOver
]
where
name' = if nodeType == NodeUser then show session else name
SettingsBox {show:showBox, add} = settingsBox nodeType
addButton p = if null add
then H.div {} []
else createNodeView d {id, name, nodeType} p
folderIcon folderOpen'@(open /\ _) =
H.a {onClick: R2.effToggler folderOpen'}
......@@ -118,7 +124,8 @@ fldr open = if open
-- START node text
type NodeTextProps =
( isSelected :: Boolean
, name :: Name )
, name :: Name
)
nodeText :: Record NodeTextProps -> R.Element
nodeText p = R.createElement el p []
......@@ -159,7 +166,8 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
[ H.div {id: "arrow"} []
, H.div { className: "panel panel-default"
, style: { border: "1px solid rgba(0,0,0,0.2)"
, boxShadow : "0 2px 5px rgba(0,0,0,0.2)"}
, boxShadow : "0 2px 5px rgba(0,0,0,0.2)"
}
}
[ panelHeading renameBoxOpen
, panelBody
......@@ -172,18 +180,16 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
, data: {toggle: "tooltip", placement: "right"}
}
rowClass true = "col-md-10"
rowClass false = "col-md-8"
rowClass false = "col-md-10"
Buttons {edit:edits,click:clicks,pop:pops} = buttons nodeType
SettingsBox {edit, add, buttons} = settingsBox nodeType
panelHeading renameBoxOpen@(open /\ _) =
H.div {className: "panel-heading"}
[ H.div {className: "row" }
[ H.div {className: "col-md-1"} []
, buttonClick d (Documentation nodeType)
, H.div {className: rowClass open} [ renameBox d {id, name} renameBoxOpen ]
, if not (null edits) then editIcon renameBoxOpen else H.div {} []
, H.div {className: "col-md-2"}
[ H.div {className: rowClass open} [ renameBox d {id, name} renameBoxOpen ]
, if edit then editIcon renameBoxOpen else H.div {} []
, H.div {className: "col-md-1"}
[ H.a {className: "btn glyphitem glyphicon glyphicon-remove-circle"
, onClick: mkEffectFn1 $ \_ -> setPopupOpen $ const Nothing
, title: "Close"} []
......@@ -192,7 +198,7 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
]
where
editIcon (false /\ setRenameBoxOpen) =
H.div {className: "col-md-2"}
H.div {className: "col-md-1"}
[ H.a {style: {color: "black"}
, className: "btn glyphitem glyphicon glyphicon-pencil"
, id: "rename1"
......@@ -209,9 +215,10 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
, justifyContent : "center"
, backgroundColor: "white"
, border: "none"}}
((map (\a -> buttonPop a setPopupOpen) pops)
$
(map (buttonClick d) buttons)
<>
(map (buttonClick d) clicks))
( [if null add then H.div {} [] else buttonPop setPopupOpen] )
nodePopupView _ p _ = R.createElement el p []
where
el = R.hooksComponent "CreateNodeView" cpt
......@@ -223,7 +230,7 @@ buttonClick _ (Documentation x ) = H.div {className: "col-md-1"}
[ H.a { style: iconAStyle
, className: (glyphicon "question-sign")
, id: "doc"
, title: "Documentation"
, title: "Documentation of " <> show x
}
-- , onClick: mkEffectFn1 $ \_ -> launchAff $ d $ DeleteNode}
[]
......@@ -257,7 +264,7 @@ buttonClick _ Download = H.div {className: "col-md-4"}
buttonClick _ _ = H.div {} []
buttonPop (Add _) f = H.div {className: "col-md-4"}
buttonPop f = H.div {className: "col-md-4"}
[ H.a { style: iconAStyle
, className: (glyphicon "plus")
, id: "create"
......@@ -267,10 +274,5 @@ buttonPop (Add _) f = H.div {className: "col-md-4"}
[]
]
buttonPop _ _ = H.div {} []
-- END Popup View
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