Commit 6cbaad00 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT][TREE] Easy Config for nodes actions

[FILES] RandomTexts in G.C.Nodes.Home
parent 8a19618a
...@@ -9,7 +9,7 @@ import Reactix.DOM.HTML as H ...@@ -9,7 +9,7 @@ import Reactix.DOM.HTML as H
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Routes (AppRoute) import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session(..), Sessions, unSessions) import Gargantext.Sessions (Session(..), Sessions, unSessions)
import Gargantext.Components.Tree (treeView) import Gargantext.Components.Forest.Tree (treeView)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
type Props = type Props =
......
module Gargantext.Components.Forest.NodeActions where
import Prelude
import Gargantext.Types
import Effect.Uncurried (mkEffectFn1)
-- import Data.Set
import Data.Array (filter)
import Reactix.DOM.HTML as H
import Effect.Aff (Aff, launchAff, runAff)
data NodeAction = Rename
| Add (Array NodeType)
| Search
| Download | Upload | Refresh
| Move | Clone | Delete
| Share
data ButtonType = Edit | 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
, pop :: Array NodeAction
}
buttons nt = Buttons {edit, click, pop}
where
edit = filter' Edit
click = filter' Click
pop = filter' Pop
filter' b = filter (\a -> buttonType a == b)
(nodeActions nt)
{-
-- | TODO use Set (needs Ord instance for NodeType)
add :: Array NodeType -> NodeAction
add = Add <<< fromFoldable
-- | TODO
filterWithRights (show action if user can only)
-}
nodeActions :: NodeType -> Array NodeAction
nodeActions NodeUser = [ Add [ FolderPrivate
, FolderTeam
, FolderPublic
]
, Delete
]
nodeActions FolderPrivate = [Add [Folder, Corpus]]
nodeActions FolderTeam = [Add [Folder, Corpus]]
nodeActions FolderPublic = [Add [Folder, Corpus]]
nodeActions Folder = [Add [Corpus], Rename, Delete]
nodeActions Corpus = [ Rename
, Search, Upload, Download
, Add [NodeList, Dashboard, Graph, Phylo]
, Share, Move , Clone
, Delete
]
nodeActions Graph = [Add [Graph], Delete]
nodeActions Texts = [Download, Upload, Delete]
nodeActions _ = []
---------------------------------------------------------
This diff is collapsed.
...@@ -123,14 +123,13 @@ instance encodeJsonTabPostQuery :: EncodeJson TabPostQuery where ...@@ -123,14 +123,13 @@ instance encodeJsonTabPostQuery :: EncodeJson TabPostQuery where
~> jsonEmptyObject ~> jsonEmptyObject
data NodeType = NodeUser data NodeType = NodeUser
| Folder | FolderPrivate | FolderTeam | FolderPublic
| Annuaire | Annuaire
| NodeContact | NodeContact
| Corpus | Corpus
| Url_Document | Url_Document
| CorpusV3
| Dashboard | Dashboard
| Error | Error
| Folder
| Graph | Graph
| Phylo | Phylo
| Individu | Individu
...@@ -144,14 +143,18 @@ derive instance eqNodeType :: Eq NodeType ...@@ -144,14 +143,18 @@ derive instance eqNodeType :: Eq NodeType
instance showNodeType :: Show NodeType where instance showNodeType :: Show NodeType where
show NodeUser = "NodeUser" show NodeUser = "NodeUser"
show Folder = "NodeFolder"
show FolderPrivate = "NodeFolderPrivate"
show FolderTeam = "NodeFolderTeam"
show FolderPublic = "NodeFolderPublic"
show Annuaire = "Annuaire" show Annuaire = "Annuaire"
show NodeContact = "NodeContact" show NodeContact = "NodeContact"
show Corpus = "NodeCorpus" show Corpus = "NodeCorpus"
show CorpusV3 = "NodeCorpusV3"
show Dashboard = "NodeDashboard" show Dashboard = "NodeDashboard"
show Url_Document = "NodeDocument" show Url_Document = "NodeDocument"
show Error = "NodeError" show Error = "NodeError"
show Folder = "NodeFolder"
show Graph = "NodeGraph" show Graph = "NodeGraph"
show Phylo = "NodePhylo" show Phylo = "NodePhylo"
show Individu = "NodeIndividu" show Individu = "NodeIndividu"
...@@ -162,18 +165,22 @@ instance showNodeType :: Show NodeType where ...@@ -162,18 +165,22 @@ instance showNodeType :: Show NodeType where
show Texts = "NodeTexts" show Texts = "NodeTexts"
readNodeType :: String -> NodeType readNodeType :: String -> NodeType
readNodeType "NodeUser" = NodeUser
readNodeType "NodeFolder" = Folder
readNodeType "NodeFolderPrivate" = FolderPrivate
readNodeType "NodeFolderTeam" = FolderTeam
readNodeType "NodeFolderPublic" = FolderPublic
readNodeType "NodeAnnuaire" = Annuaire readNodeType "NodeAnnuaire" = Annuaire
readNodeType "NodeDashboard" = Dashboard readNodeType "NodeDashboard" = Dashboard
readNodeType "Document" = Url_Document readNodeType "Document" = Url_Document
readNodeType "NodeFolder" = Folder
readNodeType "NodeGraph" = Graph readNodeType "NodeGraph" = Graph
readNodeType "NodePhylo" = Phylo readNodeType "NodePhylo" = Phylo
readNodeType "Individu" = Individu readNodeType "Individu" = Individu
readNodeType "Node" = Node readNodeType "Node" = Node
readNodeType "Nodes" = Nodes readNodeType "Nodes" = Nodes
readNodeType "NodeCorpus" = Corpus readNodeType "NodeCorpus" = Corpus
readNodeType "NodeCorpusV3" = CorpusV3
readNodeType "NodeUser" = NodeUser
readNodeType "NodeContact" = NodeContact readNodeType "NodeContact" = NodeContact
readNodeType "Tree" = Tree readNodeType "Tree" = Tree
readNodeType "NodeList" = NodeList readNodeType "NodeList" = NodeList
...@@ -197,13 +204,15 @@ instance encodeJsonNodeType :: EncodeJson NodeType where ...@@ -197,13 +204,15 @@ instance encodeJsonNodeType :: EncodeJson NodeType where
encodeJson nodeType = encodeJson $ show nodeType encodeJson nodeType = encodeJson $ show nodeType
nodeTypePath :: NodeType -> String nodeTypePath :: NodeType -> String
nodeTypePath Folder = "folder"
nodeTypePath FolderPrivate = "folderPrivate"
nodeTypePath FolderTeam = "folderTeam"
nodeTypePath FolderPublic = "folderPublic"
nodeTypePath Annuaire = "annuaire" nodeTypePath Annuaire = "annuaire"
nodeTypePath Corpus = "corpus" nodeTypePath Corpus = "corpus"
nodeTypePath CorpusV3 = "corpus"
nodeTypePath Dashboard = "dashboard" nodeTypePath Dashboard = "dashboard"
nodeTypePath Url_Document = "document" nodeTypePath Url_Document = "document"
nodeTypePath Error = "ErrorNodeType" nodeTypePath Error = "ErrorNodeType"
nodeTypePath Folder = "folder"
nodeTypePath Graph = "graph" nodeTypePath Graph = "graph"
nodeTypePath Phylo = "phylo" nodeTypePath Phylo = "phylo"
nodeTypePath Individu = "individu" nodeTypePath Individu = "individu"
......
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