Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
142
Issues
142
List
Board
Labels
Milestones
Merge Requests
4
Merge Requests
4
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
gargantext
purescript-gargantext
Commits
7b004cb5
Commit
7b004cb5
authored
Oct 17, 2019
by
Alexandre Delanoë
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[FOREST/TREE] Node refacto.
parent
235b9ba9
Changes
6
Show whitespace changes
Inline
Side-by-side
Showing
6 changed files
with
200 additions
and
114 deletions
+200
-114
Action.purs
src/Gargantext/Components/Forest/Action.purs
+13
-9
Add.purs
src/Gargantext/Components/Forest/Action/Add.purs
+24
-20
Rename.purs
src/Gargantext/Components/Forest/Action/Rename.purs
+4
-5
NodeActions.purs
src/Gargantext/Components/Forest/NodeActions.purs
+120
-46
Tree.purs
src/Gargantext/Components/Forest/Tree.purs
+12
-9
HTML.purs
src/Gargantext/Components/Forest/Tree/HTML.purs
+27
-25
No files found.
src/Gargantext/Components/Forest/Action.purs
View file @
7b004cb5
module Gargantext.Components.Forest.Action where
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.Maybe (Maybe(..), fromJust)
import Data.Newtype (class Newtype)
import Data.Newtype (class Newtype)
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Aff (Aff, launchAff, runAff)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Gargantext.Routes (AppRoute, SessionRoute(..))
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 Gargantext.Sessions (Session, sessionId, get, put, post, postWwwUrlencoded, delete)
import Data.Generic.Rep (class Generic)
import Gargantext.Types (class ToQuery, toQuery, NodeType(..), NodePath(..), readNodeType)
import Data.Generic.Rep.Show (genericShow)
import Prelude hiding (div)
import Data.Generic.Rep.Eq (genericEq)
-- file upload types
-- file upload types
data Action = Submit String
data Action = Submit String
...
@@ -18,6 +18,8 @@ data Action = Submit String
...
@@ -18,6 +18,8 @@ data Action = Submit String
| CreateSubmit String NodeType
| CreateSubmit String NodeType
| UploadFile FileType UploadFileContents
| UploadFile FileType UploadFileContents
-----------------------------------------------------
-- UploadFile Action
data FileType = CSV | PresseRIS
data FileType = CSV | PresseRIS
derive instance genericFileType :: Generic FileType _
derive instance genericFileType :: Generic FileType _
...
@@ -44,10 +46,13 @@ type FileHash = String
...
@@ -44,10 +46,13 @@ type FileHash = String
type Name = String
type Name = String
type ID = Int
type ID = Int
type Reload = Int
type Reload = Int
data NodePopup = CreatePopup | NodePopup
newtype UploadFileContents = UploadFileContents String
newtype UploadFileContents = UploadFileContents String
createNode :: Session -> ID -> CreateValue -> Aff ID
createNode :: Session -> ID -> CreateValue -> Aff ID
createNode session parentId = post session $ NodeAPI Node (Just parentId) ""
createNode session parentId = post session $ NodeAPI Node (Just parentId) ""
...
@@ -117,4 +122,3 @@ instance decodeJsonFTree :: DecodeJson (NTree LNode) where
...
@@ -117,4 +122,3 @@ instance decodeJsonFTree :: DecodeJson (NTree LNode) where
nodes' <- decodeJson nodes
nodes' <- decodeJson nodes
pure $ NTree node' nodes'
pure $ NTree node' nodes'
src/Gargantext/Components/Forest/Action/Add.purs
View file @
7b004cb5
module Gargantext.Components.Forest.Action.Add where
module Gargantext.Components.Forest.Action.Add where
import Prelude hiding (div)
import DOM.Simple.Console (log2)
import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Array (filter, null)
import Data.Array (filter, null)
...
@@ -16,7 +14,18 @@ import Effect.Aff (Aff, launchAff, runAff)
...
@@ -16,7 +14,18 @@ import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
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 Partial.Unsafe (unsafePartial)
import Prelude hiding (div)
import React.SyntheticEvent as E
import React.SyntheticEvent as E
import Reactix as R
import Reactix as R
import Reactix.DOM.HTML as H
import Reactix.DOM.HTML as H
...
@@ -26,28 +35,21 @@ import Web.File.File (toBlob)
...
@@ -26,28 +35,21 @@ import Web.File.File (toBlob)
import Web.File.FileList (FileList, item)
import Web.File.FileList (FileList, item)
import Web.File.FileReader.Aff (readAsText)
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
-- START Create Node
data NodePopup = CreatePopup | NodePopup
type CreateNodeProps =
type CreateNodeProps =
( id :: ID
( id :: ID
, name :: Name
, name :: Name
, nodeType :: NodeType)
, nodeType :: NodeType
)
createNodeView :: (Action -> Aff Unit)
createNodeView :: (Action -> Aff Unit)
-> Record CreateNodeProps
-> Record CreateNodeProps
-> R.State (Maybe NodePopup)
-> R.State (Maybe NodePopup)
-> R.Element
-> R.Element
createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
createNodeView d p
@{nodeType}
(Just CreatePopup /\ setPopupOpen) = R.createElement el p []
where
where
el = R.hooksComponent "CreateNodeView" cpt
el = R.hooksComponent "CreateNodeView" cpt
cpt {id, name} _ = do
cpt {id, name} _ = do
...
@@ -61,8 +63,10 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -61,8 +63,10 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
]
]
]
]
where
where
SettingsBox {add:nodeTypes} = settingsBox nodeType
tooltipProps = { className: ""
tooltipProps = { className: ""
, id: "
add
-node-tooltip"
, id: "
create
-node-tooltip"
, title: "Add new node"
, title: "Add new node"
, data: {toggle: "tooltip", placement: "right"}
, data: {toggle: "tooltip", placement: "right"}
}
}
...
@@ -86,7 +90,7 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -86,7 +90,7 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
[ H.div {className: "row"}
[ H.div {className: "row"}
[ H.div {className: "col-md-12"}
[ H.div {className: "col-md-12"}
[ H.form {className: "form-horizontal"}
[ H.form {className: "form-horizontal"}
[ H.div {className: "form-group"}
[
{-
H.div {className: "form-group"}
[ H.input { type: "text"
[ H.input { type: "text"
, placeholder: "Node name"
, placeholder: "Node name"
, defaultValue: name
, defaultValue: name
...
@@ -94,11 +98,11 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -94,11 +98,11 @@ createNodeView d p (Just CreatePopup /\ setPopupOpen) = R.createElement el p []
, onInput: mkEffectFn1 $ \e -> setNodeName $ const $ e .. "target" .. "value"
, onInput: mkEffectFn1 $ \e -> setNodeName $ const $ e .. "target" .. "value"
}
}
]
]
,
H.div {className: "form-group"}
, -}
H.div {className: "form-group"}
[ R2.select { className: "form-control"
[ R2.select { className: "form-control"
, onChange: mkEffectFn1 $ \e -> setNodeType $ const $ readNodeType $ e .. "target" .. "value"
, onChange: mkEffectFn1 $ \e -> setNodeType $ const $ readNodeType $ e .. "target" .. "value"
}
}
(map renderOption
[FolderPublic, FolderShared, FolderPrivate]
)
(map renderOption
nodeTypes
)
]
]
]
]
]
]
...
...
src/Gargantext/Components/Forest/Action/Rename.purs
View file @
7b004cb5
module Gargantext.Components.Forest.Action.Rename where
module Gargantext.Components.Forest.Action.Rename where
import Prelude hiding (div)
import Data.Tuple.Nested ((/\))
import Data.Tuple.Nested ((/\))
import Reactix.DOM.HTML as H
import Reactix as R
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Uncurried (mkEffectFn1)
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import FFI.Simple ((..))
import Gargantext.Components.Forest.Action
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 =
type RenameBoxProps =
( id :: ID
( id :: ID
, name :: Name)
, name :: Name)
...
...
src/Gargantext/Components/Forest/NodeActions.purs
View file @
7b004cb5
...
@@ -19,75 +19,149 @@ filterWithRights (show action if user can only)
...
@@ -19,75 +19,149 @@ filterWithRights (show action if user can only)
-}
-}
nodeActions :: NodeType -> Array NodeAction
data SettingsBox =
nodeActions NodeUser = [ Add [ FolderPrivate
SettingsBox { show :: Boolean
, edit :: Boolean
, add :: Array NodeType
, buttons :: Array NodeAction
}
settingsBox :: NodeType -> SettingsBox
settingsBox NodeUser = SettingsBox { show : true
, edit : false
, add : [ FolderPrivate
, FolderShared
, FolderShared
, FolderPublic
, FolderPublic
]
]
, buttons : [Documentation NodeUser
, Delete
, Delete
]
]
}
settingsBox FolderPrivate = SettingsBox { show: true
, edit : false
, add : [ Folder
, Corpus
]
, buttons : [Documentation FolderPrivate, Delete]
}
nodeActions FolderPrivate = [ Add [Folder, Corpus]]
settingsBox FolderShared = SettingsBox { show: true
nodeActions FolderShared = [ Add [Folder, Corpus]]
, edit : false
nodeActions FolderPublic = [ Add [Folder, Corpus]]
, 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
settingsBox Folder = SettingsBox { show : true
, Search, Upload, Download
, edit : true
, Add [NodeList, Dashboard, Graph, Phylo]
, add : [ Folder
, Share, Move , Clone
, 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
, Delete
]
]
}
nodeActions Graph = [Add [Graph], Delete]
settingsBox Texts = SettingsBox { show : true
nodeActions Texts = [Download, Upload, Delete]
, 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
data NodeAction = Documentation NodeType
| Add (Array NodeType)
| Search
| Search
| Download | Upload | Refresh
| Download | Upload | Refresh
| Move | Clone | Delete
| Move | Clone | Delete
| Share
| Share
data ButtonType = Edit | Click | Pop
data ButtonType = Click | Pop
instance eqButtonType :: Eq ButtonType where
instance eqButtonType :: Eq ButtonType where
eq Edit Edit = true
eq Click Click = true
eq Click Click = true
eq Pop Pop = true
eq Pop Pop = true
eq _ _ = false
eq _ _ = false
buttonType :: NodeAction -> ButtonType
buttonType :: NodeAction -> ButtonType
buttonType Rename = Edit
buttonType (Add _) = Pop
buttonType Search = Pop
buttonType Search = Pop
buttonType _ = Click
buttonType _ = Click
data Buttons = Buttons { edit :: Array NodeAction
data Buttons = Buttons { click :: Array NodeAction
, click :: Array NodeAction
, pop :: Array NodeAction
, pop :: Array NodeAction
}
}
buttons nt = Buttons {edit, click, pop}
{-
buttons nt = Buttons {click, pop}
where
where
edit = filter' Edit
click = init
click = filter' Click
pop = rest
pop = filter' Pop
{init, rest} = span buttonType (nodeActions nt)
filter' b = filter (\a -> buttonType a == b)
-}
(nodeActions nt)
---------------------------------------------------------
---------------------------------------------------------
src/Gargantext/Components/Forest/Tree.purs
View file @
7b004cb5
...
@@ -28,7 +28,6 @@ import Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>))
...
@@ -28,7 +28,6 @@ import Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>))
import Reactix as R
import Reactix as R
import Reactix.DOM.HTML as H
import Reactix.DOM.HTML as H
------------------------------------------------------------------------
------------------------------------------------------------------------
type Props = ( root :: ID
type Props = ( root :: ID
, mCurrentRoute :: Maybe AppRoute
, mCurrentRoute :: Maybe AppRoute
...
@@ -98,10 +97,12 @@ toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary)} /\ _)
...
@@ -98,10 +97,12 @@ toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary)} /\ _)
]
]
childNodes :: Session
childNodes :: Session -> Frontends
-> Frontends
-> R.State Reload -> R.State Boolean
-> R.State Reload
-> Maybe AppRoute -> Array FTree
-> R.State Boolean
-> Maybe AppRoute
-> Array FTree
-> Array R.Element
-> Array R.Element
childNodes _ _ _ _ _ [] = []
childNodes _ _ _ _ _ [] = []
childNodes _ _ _ (false /\ _) _ _ = []
childNodes _ _ _ (false /\ _) _ _ = []
...
@@ -116,8 +117,11 @@ childNodes session frontends reload (true /\ _) mCurrentRoute ary =
...
@@ -116,8 +117,11 @@ childNodes session frontends reload (true /\ _) mCurrentRoute ary =
pure $ toHtml reload treeState session frontends mCurrentRoute
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
performAction session (_ /\ setReload) (s@{tree: NTree (LNode {id}) _} /\ setTree) DeleteNode = do
void $ deleteNode session id
void $ deleteNode session id
liftEffect $ setReload (_ + 1)
liftEffect $ setReload (_ + 1)
...
@@ -134,4 +138,3 @@ performAction session _ ({tree: NTree (LNode {id}) _} /\ _) (UploadFile fileType
...
@@ -134,4 +138,3 @@ performAction session _ ({tree: NTree (LNode {id}) _} /\ _) (UploadFile fileType
hashes <- uploadFile session id fileType contents
hashes <- uploadFile session id fileType contents
liftEffect $ log2 "uploaded:" hashes
liftEffect $ log2 "uploaded:" hashes
src/Gargantext/Components/Forest/Tree/HTML.purs
View file @
7b004cb5
...
@@ -53,19 +53,25 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
...
@@ -53,19 +53,25 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false
isDragOver <- R.useState' false
pure $ H.span (dropProps droppedFile isDragOver)
pure $ H.span (dropProps droppedFile isDragOver)
$
[ folderIcon folderOpen
[ folderIcon folderOpen
, H.a { href: (url frontends (NodePath (sessionId session) nodeType (Just id)))
, H.a { href: (url frontends (NodePath (sessionId session) nodeType (Just id)))
, style: {marginLeft: "22px"}
, style: {marginLeft: "22px"}
}
}
[ nodeText {isSelected: (mCorpusId mCurrentRoute) == (Just id), name:name'} ]
[ nodeText { isSelected: (mCorpusId mCurrentRoute) == (Just id)
, popOverIcon popupOpen
, name: name'} ]
, nodePopupView d {id, name, nodeType} popupOpen
, if showBox then popOverIcon popupOpen else H.div {} []
, createNodeView d {id, name, nodeType} popupOpen
, if showBox then nodePopupView d {id, name:name', nodeType} popupOpen else H.div {} []
, fileTypeView d {id , nodeType} droppedFile isDragOver
, addButton popupOpen
, fileTypeView d {id, nodeType} droppedFile isDragOver
]
]
where
where
name' = if nodeType == NodeUser then show session else name
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 /\ _) =
folderIcon folderOpen'@(open /\ _) =
H.a {onClick: R2.effToggler folderOpen'}
H.a {onClick: R2.effToggler folderOpen'}
...
@@ -118,7 +124,8 @@ fldr open = if open
...
@@ -118,7 +124,8 @@ fldr open = if open
-- START node text
-- START node text
type NodeTextProps =
type NodeTextProps =
( isSelected :: Boolean
( isSelected :: Boolean
, name :: Name )
, name :: Name
)
nodeText :: Record NodeTextProps -> R.Element
nodeText :: Record NodeTextProps -> R.Element
nodeText p = R.createElement el p []
nodeText p = R.createElement el p []
...
@@ -159,7 +166,8 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -159,7 +166,8 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
[ H.div {id: "arrow"} []
[ H.div {id: "arrow"} []
, H.div { className: "panel panel-default"
, H.div { className: "panel panel-default"
, style: { border: "1px solid rgba(0,0,0,0.2)"
, 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
[ panelHeading renameBoxOpen
, panelBody
, panelBody
...
@@ -172,18 +180,16 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -172,18 +180,16 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
, data: {toggle: "tooltip", placement: "right"}
, data: {toggle: "tooltip", placement: "right"}
}
}
rowClass true = "col-md-10"
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 /\ _) =
panelHeading renameBoxOpen@(open /\ _) =
H.div {className: "panel-heading"}
H.div {className: "panel-heading"}
[ H.div {className: "row" }
[ H.div {className: "row" }
[ H.div {className: "col-md-1"} []
[ H.div {className: rowClass open} [ renameBox d {id, name} renameBoxOpen ]
, buttonClick d (Documentation nodeType)
, if edit then editIcon renameBoxOpen else H.div {} []
, H.div {className: rowClass open} [ renameBox d {id, name} renameBoxOpen ]
, H.div {className: "col-md-1"}
, if not (null edits) then editIcon renameBoxOpen else H.div {} []
, H.div {className: "col-md-2"}
[ H.a {className: "btn glyphitem glyphicon glyphicon-remove-circle"
[ H.a {className: "btn glyphitem glyphicon glyphicon-remove-circle"
, onClick: mkEffectFn1 $ \_ -> setPopupOpen $ const Nothing
, onClick: mkEffectFn1 $ \_ -> setPopupOpen $ const Nothing
, title: "Close"} []
, title: "Close"} []
...
@@ -192,7 +198,7 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -192,7 +198,7 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
]
]
where
where
editIcon (false /\ setRenameBoxOpen) =
editIcon (false /\ setRenameBoxOpen) =
H.div {className: "col-md-
2
"}
H.div {className: "col-md-
1
"}
[ H.a {style: {color: "black"}
[ H.a {style: {color: "black"}
, className: "btn glyphitem glyphicon glyphicon-pencil"
, className: "btn glyphitem glyphicon glyphicon-pencil"
, id: "rename1"
, id: "rename1"
...
@@ -209,9 +215,10 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
...
@@ -209,9 +215,10 @@ nodePopupView d p (Just NodePopup /\ setPopupOpen) = R.createElement el p []
, justifyContent : "center"
, justifyContent : "center"
, backgroundColor: "white"
, backgroundColor: "white"
, border: "none"}}
, 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 []
nodePopupView _ p _ = R.createElement el p []
where
where
el = R.hooksComponent "CreateNodeView" cpt
el = R.hooksComponent "CreateNodeView" cpt
...
@@ -223,7 +230,7 @@ buttonClick _ (Documentation x ) = H.div {className: "col-md-1"}
...
@@ -223,7 +230,7 @@ buttonClick _ (Documentation x ) = H.div {className: "col-md-1"}
[ H.a { style: iconAStyle
[ H.a { style: iconAStyle
, className: (glyphicon "question-sign")
, className: (glyphicon "question-sign")
, id: "doc"
, id: "doc"
, title: "Documentation
"
, title: "Documentation
of " <> show x
}
}
-- , onClick: mkEffectFn1 $ \_ -> launchAff $ d $ DeleteNode}
-- , onClick: mkEffectFn1 $ \_ -> launchAff $ d $ DeleteNode}
[]
[]
...
@@ -257,7 +264,7 @@ buttonClick _ Download = H.div {className: "col-md-4"}
...
@@ -257,7 +264,7 @@ buttonClick _ Download = H.div {className: "col-md-4"}
buttonClick _ _ = H.div {} []
buttonClick _ _ = H.div {} []
buttonPop
(Add _)
f = H.div {className: "col-md-4"}
buttonPop f = H.div {className: "col-md-4"}
[ H.a { style: iconAStyle
[ H.a { style: iconAStyle
, className: (glyphicon "plus")
, className: (glyphicon "plus")
, id: "create"
, id: "create"
...
@@ -267,10 +274,5 @@ buttonPop (Add _) f = H.div {className: "col-md-4"}
...
@@ -267,10 +274,5 @@ buttonPop (Add _) f = H.div {className: "col-md-4"}
[]
[]
]
]
buttonPop _ _ = H.div {} []
-- END Popup View
-- END Popup View
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment