Commit 2a38dd0a authored by Karen Konou's avatar Karen Konou

Folder actions: basic functionality

parent e1410493
...@@ -4,4 +4,10 @@ exports.back = function() { ...@@ -4,4 +4,10 @@ exports.back = function() {
return function() { return function() {
history.back(); history.back();
} }
}
exports.link = function (url) {
return function() {
window.location.href = url
}
} }
\ No newline at end of file
This diff is collapsed.
module Gargantext.Components.Forest.Tree.Node.Box where module Gargantext.Components.Forest.Tree.Node.Box where
import Gargantext.Prelude
import Data.Array as A import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), addNodeView) import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), addNodeView)
import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact
import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete) import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete)
import Gargantext.Components.Forest.Tree.Node.Action.Documentation (actionDoc) import Gargantext.Components.Forest.Tree.Node.Action.Documentation (actionDoc)
import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload) import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload)
import Gargantext.Components.Forest.Tree.Node.Action.Link (linkNode)
import Gargantext.Components.Forest.Tree.Node.Action.Merge (mergeNode)
import Gargantext.Components.Forest.Tree.Node.Action.Move (moveNode)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction) import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction)
import Gargantext.Components.Forest.Tree.Node.Action.Search (actionSearch) import Gargantext.Components.Forest.Tree.Node.Action.Search (actionSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Share as Share import Gargantext.Components.Forest.Tree.Node.Action.Share as Share
import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact
import Gargantext.Components.Forest.Tree.Node.Action.Update (update) import Gargantext.Components.Forest.Tree.Node.Action.Update (update)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload) import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload)
import Gargantext.Components.Forest.Tree.Node.Action.Move (moveNode)
import Gargantext.Components.Forest.Tree.Node.Action.Link (linkNode)
import Gargantext.Components.Forest.Tree.Node.Action.Merge (mergeNode)
import Gargantext.Components.Forest.Tree.Node.Box.Types (NodePopupProps, NodePopupS) import Gargantext.Components.Forest.Tree.Node.Box.Types (NodePopupProps, NodePopupS)
import Gargantext.Components.Forest.Tree.Node.Settings import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
(NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Status (Status(..), hasStatus) import Gargantext.Components.Forest.Tree.Node.Status (Status(..), hasStatus)
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT, panel) import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT, panel)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
...@@ -32,6 +28,9 @@ import Gargantext.Types (Name, ID, prettyNodeType) ...@@ -32,6 +28,9 @@ import Gargantext.Types (Name, ID, prettyNodeType)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (glyphicon, glyphiconActive) import Gargantext.Utils (glyphicon, glyphiconActive)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Box" here = R2.here "Gargantext.Components.Forest.Tree.Node.Box"
...@@ -82,7 +81,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where ...@@ -82,7 +81,7 @@ nodePopupCpt = here.component "nodePopupView" cpt where
, title : "Rename", on: { click: \_ -> T.write_ true isOpen } } [] , title : "Rename", on: { click: \_ -> T.write_ true isOpen } } []
panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element panelBody :: T.Box (Maybe NodeAction) -> Record NodePopupProps -> R.Element
panelBody nodePopupState {dispatch: d, nodeType} = panelBody nodePopupState {dispatch: d, nodeType} =
let (SettingsBox { edit, doc, buttons }) = settingsBox nodeType in let (SettingsBox { edit, doc, buttons}) = settingsBox nodeType in
H.div {className: "card-body flex-space-between"} H.div {className: "card-body flex-space-between"}
$ [ H.p { className: "spacer" } [] $ [ H.p { className: "spacer" } []
, H.div { className: "flex-center" } , H.div { className: "flex-center" }
......
...@@ -17,6 +17,7 @@ import Effect.Class (liftEffect) ...@@ -17,6 +17,7 @@ import Effect.Class (liftEffect)
import Effect.Exception (error) import Effect.Exception (error)
import Gargantext.Components.CodeEditor as CE import Gargantext.Components.CodeEditor as CE
import Gargantext.Components.FolderView as FV import Gargantext.Components.FolderView as FV
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Node (NodePoly(..), HyperdataList) import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData, Hyperdata(..)) import Gargantext.Components.Nodes.Corpus.Types (CorpusData, Hyperdata(..))
...@@ -37,15 +38,15 @@ import Toestand as T ...@@ -37,15 +38,15 @@ import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus" here = R2.here "Gargantext.Components.Nodes.Corpus"
type Props = ( nodeId :: Int, session :: Session ) type Props = ( nodeId :: Int, session :: Session, tasks :: T.Box GAT.Storage )
corpusLayout :: R2.Leaf Props corpusLayout :: R2.Leaf Props
corpusLayout props = R.createElement corpusLayoutCpt props [] corpusLayout props = R.createElement corpusLayoutCpt props []
corpusLayoutCpt :: R.Component Props corpusLayoutCpt :: R.Component Props
corpusLayoutCpt = here.component "corpusLayout" cpt where corpusLayoutCpt = here.component "corpusLayout" cpt where
cpt { nodeId, session } _ = do cpt { nodeId, session, tasks } _ = do
pure $ corpusLayoutMain { key, nodeId, session } pure $ corpusLayoutMain { key, nodeId, session, tasks }
where where
key = show (sessionId session) <> "-" <> show nodeId key = show (sessionId session) <> "-" <> show nodeId
...@@ -53,6 +54,7 @@ type KeyProps = ...@@ -53,6 +54,7 @@ type KeyProps =
( nodeId :: Int ( nodeId :: Int
, key :: String , key :: String
, session :: Session , session :: Session
, tasks :: T.Box GAT.Storage
) )
corpusLayoutMain :: R2.Leaf KeyProps corpusLayoutMain :: R2.Leaf KeyProps
...@@ -61,7 +63,7 @@ corpusLayoutMain props = R.createElement corpusLayoutMainCpt props [] ...@@ -61,7 +63,7 @@ corpusLayoutMain props = R.createElement corpusLayoutMainCpt props []
corpusLayoutMainCpt :: R.Component KeyProps corpusLayoutMainCpt :: R.Component KeyProps
corpusLayoutMainCpt = here.component "corpusLayoutMain" cpt corpusLayoutMainCpt = here.component "corpusLayoutMain" cpt
where where
cpt { nodeId, key, session } _ = do cpt { nodeId, key, session, tasks } _ = do
viewType <- T.useBox Folders viewType <- T.useBox Folders
pure $ H.div {} [ pure $ H.div {} [
...@@ -71,7 +73,7 @@ corpusLayoutMainCpt = here.component "corpusLayoutMain" cpt ...@@ -71,7 +73,7 @@ corpusLayoutMainCpt = here.component "corpusLayoutMain" cpt
, H.div { className: "col-1" } [ FV.homeButton ] , H.div { className: "col-1" } [ FV.homeButton ]
] ]
] ]
, H.div {} [corpusLayoutSelection {state: viewType, key, session, nodeId}] , H.div {} [corpusLayoutSelection {state: viewType, key, session, nodeId, tasks}]
] ]
type SelectionProps = type SelectionProps =
...@@ -79,6 +81,7 @@ type SelectionProps = ...@@ -79,6 +81,7 @@ type SelectionProps =
, key :: String , key :: String
, session :: Session , session :: Session
, state :: T.Box ViewType , state :: T.Box ViewType
, tasks :: T.Box GAT.Storage
) )
corpusLayoutSelection :: R2.Leaf SelectionProps corpusLayoutSelection :: R2.Leaf SelectionProps
...@@ -86,20 +89,25 @@ corpusLayoutSelection props = R.createElement corpusLayoutSelectionCpt props [] ...@@ -86,20 +89,25 @@ corpusLayoutSelection props = R.createElement corpusLayoutSelectionCpt props []
corpusLayoutSelectionCpt :: R.Component SelectionProps corpusLayoutSelectionCpt :: R.Component SelectionProps
corpusLayoutSelectionCpt = here.component "corpusLayoutSelection" cpt where corpusLayoutSelectionCpt = here.component "corpusLayoutSelection" cpt where
cpt { nodeId, session, key, state} _ = do cpt { nodeId, session, key, state, tasks} _ = do
state' <- T.useLive T.unequal state state' <- T.useLive T.unequal state
viewType <- T.read state viewType <- T.read state
pure $ renderContent viewType nodeId session key pure $ renderContent viewType nodeId session key tasks
renderContent Folders nodeId session key = FV.folderView { nodeId, session, backFolder: true } renderContent Folders nodeId session key tasks = FV.folderView { nodeId, session, backFolder: true, tasks }
renderContent Code nodeId session key = corpusLayoutWithKey { key, nodeId, session } renderContent Code nodeId session key tasks = corpusLayoutWithKey { key, nodeId, session }
type CorpusKeyProps =
( nodeId :: Int
, key :: String
, session :: Session
)
corpusLayoutWithKey :: R2.Leaf KeyProps corpusLayoutWithKey :: R2.Leaf CorpusKeyProps
corpusLayoutWithKey props = R.createElement corpusLayoutWithKeyCpt props [] corpusLayoutWithKey props = R.createElement corpusLayoutWithKeyCpt props []
corpusLayoutWithKeyCpt :: R.Component KeyProps corpusLayoutWithKeyCpt :: R.Component CorpusKeyProps
corpusLayoutWithKeyCpt = here.component "corpusLayoutWithKey" cpt where corpusLayoutWithKeyCpt = here.component "corpusLayoutWithKey" cpt where
cpt { nodeId, session } _ = do cpt { nodeId, session } _ = do
reload <- T.useBox T2.newReload reload <- T.useBox T2.newReload
......
...@@ -6,6 +6,7 @@ import Data.Array as Array ...@@ -6,6 +6,7 @@ import Data.Array as Array
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Effect (Effect) import Effect (Effect)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..)) import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.FolderView as FV import Gargantext.Components.FolderView as FV
import Gargantext.Components.Lang (LandingLang(..)) import Gargantext.Components.Lang (LandingLang(..))
...@@ -57,6 +58,7 @@ type HomeProps s l = ...@@ -57,6 +58,7 @@ type HomeProps s l =
, lang :: LandingLang , lang :: LandingLang
, sessions :: s , sessions :: s
, showLogin :: l , showLogin :: l
, tasks :: T.Box GAT.Storage
) )
homeLayout :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean homeLayout :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
...@@ -66,7 +68,7 @@ homeLayoutCpt :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean ...@@ -66,7 +68,7 @@ homeLayoutCpt :: forall s l. T.Read s Sessions => T.ReadWrite l Boolean
=> R.Component (HomeProps s l) => R.Component (HomeProps s l)
homeLayoutCpt = here.component "homeLayout" cpt homeLayoutCpt = here.component "homeLayout" cpt
where where
cpt { backend, lang, sessions, showLogin } _ = do cpt { backend, lang, sessions, showLogin, tasks} _ = do
backend' <- T.useLive T.unequal backend backend' <- T.useLive T.unequal backend
sessions' <- T.useLive T.unequal sessions sessions' <- T.useLive T.unequal sessions
let landingData = langLandingData lang let landingData = langLandingData lang
...@@ -75,7 +77,7 @@ homeLayoutCpt = here.component "homeLayout" cpt ...@@ -75,7 +77,7 @@ homeLayoutCpt = here.component "homeLayout" cpt
[ H.div { className: "home-title container1" } [ H.div { className: "home-title container1" }
[ jumboTitle landingData ] [ jumboTitle landingData ]
, H.div { className: "home-research-form container1" } [] -- TODO , H.div { className: "home-research-form container1" } [] -- TODO
, joinButtonOrTutorial sessions' (click backend') , joinButtonOrTutorial tasks sessions' (click backend')
, H.div { className: "home-public container1" } , H.div { className: "home-public container1" }
[ renderPublic { } [ renderPublic { }
, H.div { className:"col-12 d-flex justify-content-center" } , H.div { className:"col-12 d-flex justify-content-center" }
...@@ -96,11 +98,11 @@ homeLayoutCpt = here.component "homeLayout" cpt ...@@ -96,11 +98,11 @@ homeLayoutCpt = here.component "homeLayout" cpt
T.write_ true showLogin T.write_ true showLogin
Just b -> T.write_ true showLogin Just b -> T.write_ true showLogin
joinButtonOrTutorial :: forall e. Sessions -> (e -> Effect Unit) -> R.Element joinButtonOrTutorial :: forall e. T.Box GAT.Storage -> Sessions -> (e -> Effect Unit) -> R.Element
joinButtonOrTutorial sessions click = joinButtonOrTutorial tasks sessions click =
if Sessions.null sessions if Sessions.null sessions
then joinButton click then joinButton click
else tutorial {sessions: Sessions.unSessions sessions} else tutorial {tasks, sessions: Sessions.unSessions sessions}
joinButton :: forall e. (e -> Effect Unit) -> R.Element joinButton :: forall e. (e -> Effect Unit) -> R.Element
joinButton click = joinButton click =
...@@ -146,12 +148,12 @@ summary = ...@@ -146,12 +148,12 @@ summary =
, H.ol {} (map toSummary tutos) ] ] , H.ol {} (map toSummary tutos) ] ]
toSummary (Tuto x) = H.li {} [ H.a {href: "#" <> x.id} [ H.text x.title ]] toSummary (Tuto x) = H.li {} [ H.a {href: "#" <> x.id} [ H.text x.title ]]
tutorial :: R2.Leaf (sessions :: Array Session) tutorial :: R2.Leaf (sessions :: Array Session, tasks :: T.Box GAT.Storage)
tutorial props = R.createElement tutorialCpt props [] tutorial props = R.createElement tutorialCpt props []
tutorialCpt :: R.Component (sessions :: Array Session) tutorialCpt :: R.Component (sessions :: Array Session, tasks:: T.Box GAT.Storage)
tutorialCpt = here.component "tutorial" cpt where tutorialCpt = here.component "tutorial" cpt where
cpt {sessions} _ = do cpt {sessions, tasks} _ = do
let folders = makeFolders sessions let folders = makeFolders sessions
pure $ H.div { className: "mx-auto container" } pure $ H.div { className: "mx-auto container" }
...@@ -176,7 +178,7 @@ tutorialCpt = here.component "tutorial" cpt where ...@@ -176,7 +178,7 @@ tutorialCpt = here.component "tutorial" cpt where
sessionToFolder session@(Session {treeId, username, backend: (Backend {name})}) = sessionToFolder session@(Session {treeId, username, backend: (Backend {name})}) =
H.tr {} [ H.tr {} [
H.div { className: "d-flex justify-content-center" } [ H.text (username <> "@" <> name) ] H.div { className: "d-flex justify-content-center" } [ H.text (username <> "@" <> name) ]
, H.div {} [ FV.folderView {session, nodeId: treeId, backFolder: false} ] ] , H.div {} [ FV.folderView {session, tasks, nodeId: treeId, backFolder: false} ] ]
startTutos :: Array Tuto startTutos :: Array Tuto
startTutos = startTutos =
......
...@@ -279,7 +279,7 @@ corpusCpt = here.component "corpus" cpt where ...@@ -279,7 +279,7 @@ corpusCpt = here.component "corpus" cpt where
cpt props@{ boxes, nodeId } _ = do cpt props@{ boxes, nodeId } _ = do
let sessionProps = RE.pick props :: Record SessionProps let sessionProps = RE.pick props :: Record SessionProps
pure $ authed (Record.merge { content: \session -> pure $ authed (Record.merge { content: \session ->
corpusLayout { nodeId, session } } sessionProps) [] corpusLayout { nodeId, session, tasks: boxes.tasks } } sessionProps) []
type CorpusDocumentProps = type CorpusDocumentProps =
( corpusId :: CorpusId ( corpusId :: CorpusId
...@@ -340,8 +340,8 @@ home :: R2.Component Props ...@@ -340,8 +340,8 @@ home :: R2.Component Props
home = R.createElement homeCpt home = R.createElement homeCpt
homeCpt :: R.Component Props homeCpt :: R.Component Props
homeCpt = here.component "home" cpt where homeCpt = here.component "home" cpt where
cpt props@{ boxes: boxes@{ backend, sessions, showLogin } } _ = do cpt props@{ boxes: boxes@{ backend, sessions, showLogin, tasks } } _ = do
pure $ homeLayout { backend, lang: LL_EN, sessions, showLogin } pure $ homeLayout { backend, lang: LL_EN, sessions, showLogin, tasks }
lists :: R2.Component SessionNodeProps lists :: R2.Component SessionNodeProps
lists = R.createElement listsCpt lists = R.createElement listsCpt
...@@ -410,7 +410,7 @@ teamCpt = here.component "team" cpt where ...@@ -410,7 +410,7 @@ teamCpt = here.component "team" cpt where
cpt props@{ boxes, nodeId } _ = do cpt props@{ boxes, nodeId } _ = do
let sessionProps = RE.pick props :: Record SessionProps let sessionProps = RE.pick props :: Record SessionProps
pure $ authed (Record.merge { content: \session -> pure $ authed (Record.merge { content: \session ->
corpusLayout { nodeId, session } } sessionProps) [] corpusLayout { nodeId, session, tasks: boxes.tasks} } sessionProps) []
texts :: R2.Component SessionNodeProps texts :: R2.Component SessionNodeProps
texts = R.createElement textsCpt texts = R.createElement textsCpt
......
...@@ -6,4 +6,5 @@ ...@@ -6,4 +6,5 @@
.fv.action .fv.action
position: relative position: relative
left: 30px left: 30px
\ No newline at end of file color: white
\ No newline at end of file
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