Commit fb7fbcbe authored by arturo's avatar arturo

[layout] Modal reactivity for "Close" action

* #427
parent 21fc4e22
module Gargantext.Components.Bootstrap.BaseModal (baseModal) where module Gargantext.Components.Bootstrap.BaseModal
(baseModal
, showModal, hideModal
) where
import Gargantext.Prelude import Gargantext.Prelude
...@@ -109,12 +112,14 @@ component = R.hooksComponent componentName cpt where ...@@ -109,12 +112,14 @@ component = R.hooksComponent componentName cpt where
id = componentName <> "-" <> uuid id = componentName <> "-" <> uuid
selector = "#" <> id
-- | Hooks -- | Hooks
-- | -- |
useUpdateEffect1' isVisible useUpdateEffect1' isVisible
if isVisible if isVisible
then showModal window $ "#" <> id then showModal window selector
else hideModal window $ "#" <> id else hideModal window selector
-- | Behaviors -- | Behaviors
-- | -- |
......
module Gargantext.Components.FolderView where module Gargantext.Components.FolderView where
import Gargantext.Prelude
import DOM.Simple (window)
import Data.Array as A import Data.Array as A
import Data.Eq ((==))
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
import Data.Nullable (null)
import Data.Traversable (traverse_) import Data.Traversable (traverse_)
import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.BaseModal (hideModal)
import Gargantext.Components.Bootstrap.Types (Elevation(..), Variant(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (AddNodeValue(..), addNode) import Gargantext.Components.Forest.Tree.Node.Action.Add (AddNodeValue(..), addNode)
import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact
import Gargantext.Components.Forest.Tree.Node.Action.Delete (deleteNode, unpublishNode) import Gargantext.Components.Forest.Tree.Node.Action.Delete (deleteNode, unpublishNode)
...@@ -30,17 +33,14 @@ import Gargantext.Config.REST (AffRESTError, logRESTError) ...@@ -30,17 +33,14 @@ import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError) import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Hooks.LinkHandler (useLinkHandler) import Gargantext.Hooks.LinkHandler (useLinkHandler)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Ordering, Unit, bind, compare, discard, otherwise, pure, unit, void, ($), (<$>), (<>))
import Gargantext.Routes (AppRoute(Home), nodeTypeAppRoute) import Gargantext.Routes (AppRoute(Home), nodeTypeAppRoute)
import Gargantext.Sessions (Session(..), sessionId) import Gargantext.Sessions (Session(..), sessionId)
import Gargantext.Types (NodeType(..), SessionId) import Gargantext.Types (NodeType(..), SessionId)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Record as Record
import Toestand as T import Toestand as T
here :: R2.Here here :: R2.Here
...@@ -59,7 +59,6 @@ folderView = R2.leafComponent folderViewCpt ...@@ -59,7 +59,6 @@ folderView = R2.leafComponent folderViewCpt
folderViewCpt :: R.Component Props folderViewCpt :: R.Component Props
folderViewCpt = here.component "folderViewCpt" cpt where folderViewCpt = here.component "folderViewCpt" cpt where
cpt { boxes, nodeId, session } _ = do cpt { boxes, nodeId, session } _ = do
setPopoverRef <- R.useRef Nothing
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload reload' <- T.useLive T.unequal reload
useLoader { errorHandler useLoader { errorHandler
...@@ -70,7 +69,7 @@ folderViewCpt = here.component "folderViewCpt" cpt where ...@@ -70,7 +69,7 @@ folderViewCpt = here.component "folderViewCpt" cpt where
, nodeId , nodeId
, reload , reload
, session , session
, setPopoverRef } [] } } [] }
where where
errorHandler = logRESTError here "[folderView]" errorHandler = logRESTError here "[folderView]"
...@@ -80,7 +79,6 @@ type FolderViewProps = ...@@ -80,7 +79,6 @@ type FolderViewProps =
, nodeId :: Int , nodeId :: Int
, reload :: T.Box T2.Reload , reload :: T.Box T2.Reload
, session :: Session , session :: Session
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
) )
folderViewMain :: R2.Component FolderViewProps folderViewMain :: R2.Component FolderViewProps
...@@ -105,13 +103,15 @@ folderViewMainCpt = here.component "folderViewMainCpt" cpt where ...@@ -105,13 +103,15 @@ folderViewMainCpt = here.component "folderViewMainCpt" cpt where
, parentId: props.nodeId , parentId: props.nodeId
, reload: props.reload , reload: props.reload
, session: props.session , session: props.session
, setPopoverRef: props.setPopoverRef
, style: FolderChild , style: FolderChild
, text: node.name } [] , text: node.name
}
makeParentFolder :: TreeNode -> Maybe TreeNode -> Record FolderViewProps -> Array R.Element makeParentFolder :: TreeNode -> Maybe TreeNode -> Record FolderViewProps -> Array R.Element
makeParentFolder root (Just parent) props = makeParentFolder root (Just parent) props =
[ folder { boxes: props.boxes [
folder
{ boxes: props.boxes
, nodeId: root.id , nodeId: root.id
, linkId: parent.id , linkId: parent.id
, linkNodeType: parent.node_type , linkNodeType: parent.node_type
...@@ -119,9 +119,10 @@ folderViewMainCpt = here.component "folderViewMainCpt" cpt where ...@@ -119,9 +119,10 @@ folderViewMainCpt = here.component "folderViewMainCpt" cpt where
, parentId: parent.id , parentId: parent.id
, reload: props.reload , reload: props.reload
, session: props.session , session: props.session
, setPopoverRef: props.setPopoverRef
, style: FolderUp , style: FolderUp
, text: root.name } [] ] , text: root.name
}
]
makeParentFolder _ Nothing _ = [] makeParentFolder _ Nothing _ = []
sortFolders :: TreeNode-> TreeNode -> Ordering sortFolders :: TreeNode-> TreeNode -> Ordering
...@@ -138,11 +139,10 @@ type FolderProps = ...@@ -138,11 +139,10 @@ type FolderProps =
, boxes :: Boxes , boxes :: Boxes
, parentId :: Int , parentId :: Int
, reload :: T.Box T2.Reload , reload :: T.Box T2.Reload
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
) )
folder :: R2.Component FolderProps folder :: R2.Leaf FolderProps
folder = R.createElement folderCpt folder = R2.leaf folderCpt
folderCpt :: R.Component FolderProps folderCpt :: R.Component FolderProps
folderCpt = here.component "folderCpt" cpt where folderCpt = here.component "folderCpt" cpt where
cpt props@{ boxes cpt props@{ boxes
...@@ -153,57 +153,71 @@ folderCpt = here.component "folderCpt" cpt where ...@@ -153,57 +153,71 @@ folderCpt = here.component "folderCpt" cpt where
, parentId , parentId
, reload , reload
, session , session
, setPopoverRef
, style , style
, text } _ = do , text
let sid = sessionId session } _ = do
let rootId = treeId session -- States
let dispatch a = performAction a { boxes, nodeId, parentId, reload, session, setPopoverRef } isBoxVisible <- T.useBox false
popoverRef <- R.useRef null
-- Hooks
{ goToRoute } <- useLinkHandler { goToRoute } <- useLinkHandler
R.useEffect' $ do -- Computed
R.setRef setPopoverRef $ Just $ Popover.setOpen popoverRef let sid = sessionId session
let rootId = treeId session
let dispatch a = performAction a { boxes, nodeId, parentId, reload, session, isBoxVisible }
-- Render
pure $ pure $
H.div {}
[ H.span { style: { position: "absolute" } } H.div
[ Popover.popover { {}
arrow: false [
, open: false B.iconButton
, onClose: \_ -> pure unit { name: "cog"
, onOpen: \_ -> pure unit , callback: \_ -> T.write_ true isBoxVisible
, ref: popoverRef , title:
"Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them."
, variant: Secondary
, elevation: Level0
, overlay: false
} }
[ popOverIcon ,
, mNodePopupView (Record.merge props { dispatch }) (onPopoverClose popoverRef) H.button
] { className: "btn btn-primary fv btn"
]
, H.button { className: "btn btn-primary fv btn"
, on: { click: \_ -> goToRoute $ route linkId rootId linkNodeType sid } , on: { click: \_ -> goToRoute $ route linkId rootId linkNodeType sid }
} }
[ H.i {className: icon style nodeType} [] [
, H.br {} H.i
, H.text text { className: icon style nodeType }
] []
] ,
H.br {}
onPopoverClose popoverRef _ = Popover.setOpen popoverRef false ,
H.text text
popOverIcon = H.span { className: "fv action" }
[ H.a { className: "settings fa fa-cog"
, title : "Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them." } []
] ]
,
mNodePopupView props opc = nodePopupView { boxes: props.boxes -- // Modals //
, dispatch: props.dispatch B.baseModal
{ isVisibleBox: isBoxVisible
, noBody: true
, noHeader: true
, modalClassName: "forest-tree-node-modal"
}
[
nodePopupView
{ boxes: props.boxes
, dispatch: dispatch
, id: props.nodeId , id: props.nodeId
, onPopoverClose: opc
, nodeType: props.nodeType , nodeType: props.nodeType
, name: props.text , name: props.text
, session: props.session , session: props.session
, closeCallback: \_ -> T.write_ false isBoxVisible
} }
]
]
route :: Int -> Int -> NodeType -> SessionId -> AppRoute route :: Int -> Int -> NodeType -> SessionId -> AppRoute
route lId rootId nType sid route lId rootId nType sid
| rootId == lId = Home | rootId == lId = Home
...@@ -289,8 +303,8 @@ type PerformActionProps = ...@@ -289,8 +303,8 @@ type PerformActionProps =
, nodeId :: Int , nodeId :: Int
, parentId :: Int , parentId :: Int
, reload :: T.Box T2.Reload , reload :: T.Box T2.Reload
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit))
, session :: Session , session :: Session
, isBoxVisible :: T.Box Boolean
) )
performAction :: Action -> Record PerformActionProps -> Aff Unit performAction :: Action -> Record PerformActionProps -> Aff Unit
...@@ -312,16 +326,30 @@ performAction = performAction' where ...@@ -312,16 +326,30 @@ performAction = performAction' where
performAction' (MergeNode {params}) p = mergeNode params p performAction' (MergeNode {params}) p = mergeNode params p
performAction' (LinkNode { nodeType, params }) p = linkNode nodeType params p performAction' (LinkNode { nodeType, params }) p = linkNode nodeType params p
performAction' NoAction _ = liftEffect $ here.log "[performAction] NoAction" performAction' NoAction _ = liftEffect $ here.log "[performAction] NoAction"
performAction' ClosePopover p = closePopover p performAction' CloseBox p = closeBox p
performAction' _ _ = liftEffect $ here.log "[performAction] unsupported action" performAction' _ _ = liftEffect $ here.log "[performAction] unsupported action"
closePopover { setPopoverRef } = closeBox { isBoxVisible, nodeId } =
liftEffect $ traverse_ (\set -> set false) (R.readRef setPopoverRef) liftEffect $ do
T.write_ false isBoxVisible
-- @XXX ReactJS unreactive ref
--
-- /!\ extra care here:
--
-- - due to a ReactJS yet another flaw, we have to make an extra closing
-- modal method call here (bc. even if the `T.Box` change its value
-- no reactivity will be perfomed, for some unknown reason, and
-- the modal would so partially close)
--
-- - also make an extra assumption here, as the `querySelector` used for
-- modal close call should be the same as the selector qualifying the
-- created <base-modal>)
hideModal window $ "#" <> (show nodeId)
refreshFolders p@{ boxes: { reloadForest }, reload } = do refreshFolders p@{ boxes: { reloadForest }, reload } = do
liftEffect $ T2.reload reload liftEffect $ T2.reload reload
liftEffect $ T2.reload reloadForest liftEffect $ T2.reload reloadForest
closePopover p closeBox p
deleteNode' nt p@{ nodeId: id, parentId: parent_id, session } = do deleteNode' nt p@{ nodeId: id, parentId: parent_id, session } = do
case nt of case nt of
......
...@@ -42,7 +42,7 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where ...@@ -42,7 +42,7 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where
] ]
] ]
closePopover props = props.onPopoverClose <<< R.unsafeEventTarget closeBox props = props.onPopoverClose <<< R.unsafeEventTarget
panelHeading props@{ nodeType } = panelHeading props@{ nodeType } =
H.div { className: "popup-container__header card-header" } H.div { className: "popup-container__header card-header" }
...@@ -53,5 +53,5 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where ...@@ -53,5 +53,5 @@ nodePopupViewCpt = here.component "nodePopupView" cpt where
, H.div { className: "col-6" } , H.div { className: "col-6" }
[ H.span { className: "text-primary center" } [ H.text props.name ] ] [ H.span { className: "text-primary center" } [ H.text props.name ] ]
, H.div { className: "col-1" } , H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover props }, title: "Close" [ H.a { type: "button", on: { click: closeBox props }, title: "Close"
, className: glyphicon "window-close" } [] ]]] , className: glyphicon "window-close" } [] ]]]
...@@ -7,7 +7,6 @@ import Data.Array as Array ...@@ -7,7 +7,6 @@ import Data.Array as Array
import Data.Maybe (Maybe(..), isJust) import Data.Maybe (Maybe(..), isJust)
import Data.Traversable (intercalate, traverse, traverse_) import Data.Traversable (intercalate, traverse, traverse_)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
...@@ -31,13 +30,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(.. ...@@ -31,13 +30,13 @@ import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut(..
import Gargantext.Config.REST (AffRESTError, logRESTError) import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Config.Utils (handleRESTError) import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader, useLoaderEffect) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Sessions (Session, get, mkNodeId) import Gargantext.Sessions (Session, get, mkNodeId)
import Gargantext.Sessions.Types (useOpenNodesMemberBox, openNodesInsert, openNodesDelete) import Gargantext.Sessions.Types (useOpenNodesMemberBox, openNodesInsert, openNodesDelete)
import Gargantext.Types (Handed, ID, isPublic, publicize, switchHanded) import Gargantext.Types (Handed, ID, isPublic, publicize)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (nbsp, (?)) import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
...@@ -99,11 +98,13 @@ type ChildLoaderProps = ...@@ -99,11 +98,13 @@ type ChildLoaderProps =
( id :: ID ( id :: ID
, render :: R2.Leaf TreeProps , render :: R2.Leaf TreeProps
, root :: ID , root :: ID
| NodeProps ) | NodeProps
)
type PerformActionProps = type PerformActionProps =
( setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit)) ( isBoxVisible :: T.Box Boolean
| PACommon ) | PACommon
)
-- | Loads and renders the tree starting at the given root node id. -- | Loads and renders the tree starting at the given root node id.
treeLoader :: R2.Leaf ( key :: String | LoaderProps ) treeLoader :: R2.Leaf ( key :: String | LoaderProps )
...@@ -163,7 +164,7 @@ treeCpt = here.component "tree" cpt where ...@@ -163,7 +164,7 @@ treeCpt = here.component "tree" cpt where
, session , session
, tree: NTree (LNode { id, name, nodeType }) children } _ = do , tree: NTree (LNode { id, name, nodeType }) children } _ = do
setPopoverRef <- R.useRef Nothing isBoxVisible <- T.useBox false
folderOpen <- useOpenNodesMemberBox nodeId forestOpen folderOpen <- useOpenNodesMemberBox nodeId forestOpen
folderOpen' <- T.useLive T.unequal folderOpen folderOpen' <- T.useLive T.unequal folderOpen
...@@ -183,7 +184,7 @@ treeCpt = here.component "tree" cpt where ...@@ -183,7 +184,7 @@ treeCpt = here.component "tree" cpt where
[ [
nodeSpan nodeSpan
{ boxes { boxes
, dispatch: dispatch setPopoverRef , dispatch: dispatch' isBoxVisible
, folderOpen , folderOpen
, frontends , frontends
, id , id
...@@ -193,7 +194,7 @@ treeCpt = here.component "tree" cpt where ...@@ -193,7 +194,7 @@ treeCpt = here.component "tree" cpt where
, reload , reload
, root , root
, session , session
, setPopoverRef , isBoxVisible
} }
<> <>
R2.when (folderOpen') R2.when (folderOpen')
...@@ -213,9 +214,9 @@ treeCpt = here.component "tree" cpt where ...@@ -213,9 +214,9 @@ treeCpt = here.component "tree" cpt where
nodeId = mkNodeId session id nodeId = mkNodeId session id
children' = A.sortWith fTreeID pubChildren children' = A.sortWith fTreeID pubChildren
pubChildren = if isPublic nodeType then map (map pub) children else children pubChildren = if isPublic nodeType then map (map pub) children else children
dispatch setPopoverRef a = performAction a (Record.merge common' spr) where dispatch' isBoxVisible a = performAction a (Record.merge common' extra) where
common' = RecordE.pick p :: Record PACommon common' = RecordE.pick p :: Record PACommon
spr = { setPopoverRef } extra = { isBoxVisible }
pub (LNode n@{ nodeType: t }) = LNode (n { nodeType = publicize t }) pub (LNode n@{ nodeType: t }) = LNode (n { nodeType = publicize t })
...@@ -295,10 +296,10 @@ childLoaderCpt = here.component "childLoader" cpt where ...@@ -295,10 +296,10 @@ childLoaderCpt = here.component "childLoader" cpt where
extra = { root, tree: tree' } extra = { root, tree: tree' }
nodeProps = RecordE.pick p :: Record NodeProps nodeProps = RecordE.pick p :: Record NodeProps
closePopover { setPopoverRef } = closeBox { isBoxVisible } =
liftEffect $ traverse_ (\set -> set false) (R.readRef setPopoverRef) liftEffect $ T.write_ false isBoxVisible
refreshTree p@{ reloadTree } = liftEffect $ T2.reload reloadTree *> closePopover p refreshTree p@{ reloadTree } = liftEffect $ T2.reload reloadTree *> closeBox p
deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, parent_id}) _) } = do deleteNode' nt p@{ boxes: { forestOpen }, session, tree: (NTree (LNode {id, parent_id}) _) } = do
case nt of case nt of
...@@ -407,6 +408,6 @@ performAction (MoveNode {params}) p = moveNode params ...@@ -407,6 +408,6 @@ performAction (MoveNode {params}) p = moveNode params
performAction (MergeNode {params}) p = mergeNode params p performAction (MergeNode {params}) p = mergeNode params p
performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p performAction (LinkNode { nodeType, params }) p = linkNode nodeType params p
performAction RefreshTree p = refreshTree p performAction RefreshTree p = refreshTree p
performAction ClosePopover p = closePopover p performAction CloseBox p = closeBox p
performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p performAction (DocumentsFromWriteNodes { id }) p = documentsFromWriteNodes id p
performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction" performAction NoAction _ = liftEffect $ here.log "[performAction] NoAction"
...@@ -8,7 +8,6 @@ import Gargantext.Prelude ...@@ -8,7 +8,6 @@ import Gargantext.Prelude
import Data.Array.NonEmpty as NArray import Data.Array.NonEmpty as NArray
import Data.Foldable (intercalate) import Data.Foldable (intercalate)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Nullable (null)
import Data.String.Regex as Regex import Data.String.Regex as Regex
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -18,7 +17,7 @@ import Effect.Class (liftEffect) ...@@ -18,7 +17,7 @@ import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), Elevation(..), ModalSizing(..), TooltipEffect(..), Variant(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), Elevation(..), TooltipEffect(..), Variant(..))
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Upload (DroppedFile(..), fileTypeView) import Gargantext.Components.Forest.Tree.Node.Action.Upload (DroppedFile(..), fileTypeView)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileBlob(..)) import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileBlob(..))
...@@ -31,7 +30,6 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) ...@@ -31,7 +30,6 @@ import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Config.REST (logRESTError) import Gargantext.Config.REST (logRESTError)
import Gargantext.Context.Progress (asyncContext, asyncProgress) import Gargantext.Context.Progress (asyncContext, asyncProgress)
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.FirstEffect (useFirstEffect')
import Gargantext.Hooks.Loader (useLoaderEffect) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Hooks.Version (Version, useVersion) import Gargantext.Hooks.Version (Version, useVersion)
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
...@@ -39,7 +37,6 @@ import Gargantext.Sessions (Session, sessionId) ...@@ -39,7 +37,6 @@ import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (ID, Name) import Gargantext.Types (ID, Name)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (nbsp, textEllipsisBreak, (?)) import Gargantext.Utils (nbsp, textEllipsisBreak, (?))
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import React.SyntheticEvent as SE import React.SyntheticEvent as SE
...@@ -47,7 +44,6 @@ import Reactix as R ...@@ -47,7 +44,6 @@ import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Record as Record import Record as Record
import Toestand as T import Toestand as T
import Unsafe.Coerce (unsafeCoerce)
-- (?) never been able to properly declare PureScript Regex... -- (?) never been able to properly declare PureScript Regex...
foreign import nodeUserRegexp :: Regex.Regex foreign import nodeUserRegexp :: Regex.Regex
...@@ -68,7 +64,7 @@ type NodeSpanProps = ...@@ -68,7 +64,7 @@ type NodeSpanProps =
, reload :: T2.ReloadS , reload :: T2.ReloadS
, root :: ID , root :: ID
, session :: Session , session :: Session
, setPopoverRef :: R.Ref (Maybe (Boolean -> Effect Unit)) , isBoxVisible :: T.Box Boolean
) )
type IsLeaf = Boolean type IsLeaf = Boolean
...@@ -92,7 +88,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -92,7 +88,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, nodeType , nodeType
, reload , reload
, session , session
, setPopoverRef , isBoxVisible
} _ = do } _ = do
-- States -- States
...@@ -108,8 +104,6 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -108,8 +104,6 @@ nodeSpanCpt = here.component "nodeSpan" cpt
folderOpen' <- R2.useLive' folderOpen folderOpen' <- R2.useLive' folderOpen
isSettingsModalVisible <- T.useBox false
-- tasks' <- T.read tasks -- tasks' <- T.read tasks
-- Computed -- Computed
...@@ -198,18 +192,10 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -198,18 +192,10 @@ nodeSpanCpt = here.component "nodeSpan" cpt
-- Nothing -> pure unit -- Nothing -> pure unit
-- T2.reload reloadRoot -- T2.reload reloadRoot
onPopoverClose ::
Popover.PopoverRef
-> Effect Unit
onPopoverClose ref = Popover.setOpen ref false
-- NOTE Don't toggle tree if it is not selected -- NOTE Don't toggle tree if it is not selected
onNodeLinkClick :: Unit -> Effect Unit onNodeLinkClick :: Unit -> Effect Unit
onNodeLinkClick _ = when (not isSelected) (T.write_ true folderOpen) onNodeLinkClick _ = when (not isSelected) (T.write_ true folderOpen)
toggleSettingsModal :: Unit -> Effect Unit
toggleSettingsModal _ = T.modify_ (not) isSettingsModalVisible
-- Hooks -- Hooks
mVersion <- useVersion $ nodeType == GT.NodeUser ? mVersion <- useVersion $ nodeType == GT.NodeUser ?
...@@ -320,7 +306,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -320,7 +306,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
B.iconButton B.iconButton
{ name: "cog" { name: "cog"
, className: "mainleaf__settings-icon" , className: "mainleaf__settings-icon"
, callback: toggleSettingsModal , callback: \_ -> T.write_ true isBoxVisible
, title: , title:
"Each node of the Tree can perform some actions.\n" "Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them." <> "Click here to execute one of them."
...@@ -346,7 +332,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -346,7 +332,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
-- // Modals // -- // Modals //
B.baseModal B.baseModal
{ isVisibleBox: isSettingsModalVisible { isVisibleBox: isBoxVisible
, noBody: true , noBody: true
, noHeader: true , noHeader: true
, modalClassName: "forest-tree-node-modal" , modalClassName: "forest-tree-node-modal"
...@@ -358,7 +344,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt ...@@ -358,7 +344,7 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, id , id
, name , name
, nodeType , nodeType
, onPopoverClose: \_ -> toggleSettingsModal unit , closeCallback: \_ -> T.write_ false isBoxVisible
, session , session
} }
] ]
......
...@@ -46,7 +46,7 @@ icon (UploadFile _ _ _ _ _ _) = glyphiconNodeAction Upload ...@@ -46,7 +46,7 @@ icon (UploadFile _ _ _ _ _ _) = glyphiconNodeAction Upload
icon (UploadArbitraryFile _ _ _ _ ) = glyphiconNodeAction Upload icon (UploadArbitraryFile _ _ _ _ ) = glyphiconNodeAction Upload
icon UploadFrameCalc = glyphiconNodeAction Upload icon UploadFrameCalc = glyphiconNodeAction Upload
icon RefreshTree = glyphiconNodeAction Refresh icon RefreshTree = glyphiconNodeAction Refresh
icon ClosePopover = glyphiconNodeAction CloseNodePopover icon CloseBox = glyphiconNodeAction CloseNodePopover
icon DownloadNode = glyphiconNodeAction Download icon DownloadNode = glyphiconNodeAction Download
icon (MoveNode _ ) = glyphiconNodeAction (Move { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }}) icon (MoveNode _ ) = glyphiconNodeAction (Move { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
icon (MergeNode _ ) = glyphiconNodeAction (Merge { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }}) icon (MergeNode _ ) = glyphiconNodeAction (Merge { subTreeParams : SubTreeParams {showtypes:[], valitypes:[] }})
...@@ -70,7 +70,7 @@ text (UploadFile _ _ _ _ _ _) = "Upload File !" ...@@ -70,7 +70,7 @@ text (UploadFile _ _ _ _ _ _) = "Upload File !"
text (UploadArbitraryFile _ _ _ _) = "Upload arbitrary file !" text (UploadArbitraryFile _ _ _ _) = "Upload arbitrary file !"
text UploadFrameCalc = "Upload frame calc" text UploadFrameCalc = "Upload frame calc"
text RefreshTree = "Refresh Tree !" text RefreshTree = "Refresh Tree !"
text ClosePopover = "Close Popover !" text CloseBox = "Close Box !"
text DownloadNode = "Download !" text DownloadNode = "Download !"
text (MoveNode _ ) = "Move !" text (MoveNode _ ) = "Move !"
text (MergeNode _ ) = "Merge !" text (MergeNode _ ) = "Merge !"
...@@ -78,4 +78,3 @@ text (LinkNode _ ) = "Link !" ...@@ -78,4 +78,3 @@ text (LinkNode _ ) = "Link !"
text (DocumentsFromWriteNodes _ ) = "Documents from Write Nodes !" text (DocumentsFromWriteNodes _ ) = "Documents from Write Nodes !"
text NoAction = "No Action" text NoAction = "No Action"
----------------------------------------------------------------------- -----------------------------------------------------------------------
...@@ -54,7 +54,7 @@ actionSearchCpt = here.component "actionSearch" cpt ...@@ -54,7 +54,7 @@ actionSearchCpt = here.component "actionSearch" cpt
searchOn dispatch' task = do searchOn dispatch' task = do
_ <- launchAff $ dispatch' (DoSearch task) _ <- launchAff $ dispatch' (DoSearch task)
-- close popup -- close popup
_ <- launchAff $ dispatch' ClosePopover _ <- launchAff $ dispatch' CloseBox
-- TODO -- TODO
--snd p $ const Nothing --snd p $ const Nothing
pure unit pure unit
...@@ -21,7 +21,7 @@ data Action = AddNode String GT.NodeType ...@@ -21,7 +21,7 @@ data Action = AddNode String GT.NodeType
| UploadFrameCalc | UploadFrameCalc
| DownloadNode | DownloadNode
| RefreshTree | RefreshTree
| ClosePopover | CloseBox
| ShareTeam String | ShareTeam String
| AddContact AddContactParams | AddContact AddContactParams
...@@ -48,7 +48,7 @@ instance Eq Action where ...@@ -48,7 +48,7 @@ instance Eq Action where
eq UploadFrameCalc UploadFrameCalc = true eq UploadFrameCalc UploadFrameCalc = true
eq DownloadNode DownloadNode = true eq DownloadNode DownloadNode = true
eq RefreshTree RefreshTree = true eq RefreshTree RefreshTree = true
eq ClosePopover ClosePopover = true eq CloseBox CloseBox = true
eq (ShareTeam s1) (ShareTeam s2) = eq s1 s2 eq (ShareTeam s1) (ShareTeam s2) = eq s1 s2
eq (AddContact ac1) (AddContact ac2) = eq ac1 ac2 eq (AddContact ac1) (AddContact ac2) = eq ac1 ac2
eq (SharePublic p1) (SharePublic p2) = eq p1 p2 eq (SharePublic p1) (SharePublic p2) = eq p1 p2
...@@ -72,7 +72,7 @@ instance Show Action where ...@@ -72,7 +72,7 @@ instance Show Action where
show (UploadArbitraryFile _ _ _ _) = "UploadArbitraryFile" show (UploadArbitraryFile _ _ _ _) = "UploadArbitraryFile"
show UploadFrameCalc = "UploadFrameCalc" show UploadFrameCalc = "UploadFrameCalc"
show RefreshTree = "RefreshTree" show RefreshTree = "RefreshTree"
show ClosePopover = "ClosePopover" show CloseBox = "CloseBox"
show DownloadNode = "Download" show DownloadNode = "Download"
show (MoveNode _ ) = "MoveNode" show (MoveNode _ ) = "MoveNode"
show (MergeNode _ ) = "MergeNode" show (MergeNode _ ) = "MergeNode"
......
...@@ -86,7 +86,7 @@ updateGraphCpt = here.component "updateGraph" cpt where ...@@ -86,7 +86,7 @@ updateGraphCpt = here.component "updateGraph" cpt where
let let
callback :: Action -> Aff Unit callback :: Action -> Aff Unit
callback = dispatch >=> \_ -> dispatch ClosePopover callback = dispatch >=> \_ -> dispatch CloseBox
pure $ panel [ H.text "Show subjects with Order1 or concepts with Order2 ?" pure $ panel [ H.text "Show subjects with Order1 or concepts with Order2 ?"
, formChoiceSafe { items: [Order1, Order2] , formChoiceSafe { items: [Order1, Order2]
...@@ -153,7 +153,7 @@ updatePhyloCpt = here.component "updatePhylo" cpt where ...@@ -153,7 +153,7 @@ updatePhyloCpt = here.component "updatePhylo" cpt where
opts <- pure $ options r' opts <- pure $ options r'
launchAff_ do launchAff_ do
dispatch opts dispatch opts
dispatch ClosePopover dispatch CloseBox
where where
options :: Phylo.UpdateData -> Action options :: Phylo.UpdateData -> Action
......
...@@ -265,7 +265,7 @@ uploadButtonCpt = here.component "uploadButton" cpt ...@@ -265,7 +265,7 @@ uploadButtonCpt = here.component "uploadButton" cpt
T.write_ Plain fileFormat T.write_ Plain fileFormat
T.write_ EN lang T.write_ EN lang
T.write_ false onPendingBox T.write_ false onPendingBox
dispatch ClosePopover dispatch CloseBox
uploadListView :: R2.Leaf Props uploadListView :: R2.Leaf Props
uploadListView = R2.leafComponent uploadListViewCpt uploadListView = R2.leafComponent uploadListViewCpt
......
...@@ -40,7 +40,8 @@ here = R2.here "Gargantext.Components.Forest.Tree.Node.Box" ...@@ -40,7 +40,8 @@ here = R2.here "Gargantext.Components.Forest.Tree.Node.Box"
type CommonProps = type CommonProps =
( dispatch :: Action -> Aff Unit ( dispatch :: Action -> Aff Unit
, session :: Session ) , session :: Session
)
nodePopupView :: R2.Leaf NodePopupProps nodePopupView :: R2.Leaf NodePopupProps
nodePopupView = R2.leafComponent nodePopupCpt nodePopupView = R2.leafComponent nodePopupCpt
...@@ -71,7 +72,6 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -71,7 +72,6 @@ nodePopupCpt = here.component "nodePopupView" cpt where
] ]
] ]
closePopover p = p.onPopoverClose <<< R.unsafeEventTarget
panelHeading renameIsOpen open p@{ dispatch, id, name, nodeType } = panelHeading renameIsOpen open p@{ dispatch, id, name, nodeType } =
H.div { className: "popup-container__header card-header" } H.div { className: "popup-container__header card-header" }
[ R2.row [ R2.row
...@@ -86,7 +86,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -86,7 +86,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
] ]
, H.div { className: "col-1" } [ editIcon renameIsOpen open ] , H.div { className: "col-1" } [ editIcon renameIsOpen open ]
, H.div { className: "col-1" } , H.div { className: "col-1" }
[ H.a { type: "button", on: { click: closePopover p }, title: "Close" [ H.a { type: "button", on: { click: \_ -> p.closeCallback unit }, title: "Close"
, className: glyphicon "window-close" } [] ]]] , className: glyphicon "window-close" } [] ]]]
editIcon _ true = H.div {} [] editIcon _ true = H.div {} []
editIcon isOpen false = editIcon isOpen false =
......
module Gargantext.Components.Forest.Tree.Node.Box.Types where module Gargantext.Components.Forest.Tree.Node.Box.Types where
import DOM.Simple as DOM
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
...@@ -22,7 +21,7 @@ type NodePopupProps = ...@@ -22,7 +21,7 @@ type NodePopupProps =
, id :: ID , id :: ID
, name :: Name , name :: Name
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, onPopoverClose :: DOM.Element -> Effect Unit , closeCallback :: Unit -> Effect Unit
| CommonProps | CommonProps
) )
......
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