Commit ab4c05a4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT] Box update/refresh + fix warnings

parent d83ff5b7
...@@ -2,29 +2,16 @@ module Gargantext.Components.Forest.Tree.Node where ...@@ -2,29 +2,16 @@ module Gargantext.Components.Forest.Tree.Node where
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Nullable (null) import Data.Nullable (null)
import Data.String as S
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1) import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), settingsBox)
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileContents(..)) import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), addNodeView) import Gargantext.Components.Forest.Tree.Node.Action.Upload (DroppedFile(..), fileTypeView)
import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (copyFromCorpusView)
import Gargantext.Components.Forest.Tree.Node.Action.Documentation (actionDoc)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction)
import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete)
import Gargantext.Components.Forest.Tree.Node.Action.Search (actionSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Share as Share
import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload, DroppedFile(..), fileTypeView)
import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload)
import Gargantext.Components.Forest.Tree.Node.Box (nodePopupView) import Gargantext.Components.Forest.Tree.Node.Box (nodePopupView)
import Gargantext.Components.Forest.Tree.Node.Box.Types (CommonProps, NodePopupProps, NodePopupS) import Gargantext.Components.Forest.Tree.Node.Box.Types (CommonProps)
import Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar (asyncProgressBar, BarType(..)) import Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar (asyncProgressBar, BarType(..))
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT)
import Gargantext.Components.Forest.Tree.Node.Tools.Task (Tasks) import Gargantext.Components.Forest.Tree.Node.Tools.Task (Tasks)
import Gargantext.Components.Forest.Tree.Node.Tools.Sync (nodeActionsGraph, nodeActionsNodeList) import Gargantext.Components.Forest.Tree.Node.Tools.Sync (nodeActionsGraph, nodeActionsNodeList)
import Gargantext.Components.GraphExplorer.API as GraphAPI import Gargantext.Components.GraphExplorer.API as GraphAPI
...@@ -37,7 +24,6 @@ import Gargantext.Routes as Routes ...@@ -37,7 +24,6 @@ import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId) import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (Name, ID) import Gargantext.Types (Name, ID)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (glyphicon, glyphiconActive)
import Gargantext.Utils.Popover as Popover import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import React.SyntheticEvent as E import React.SyntheticEvent as E
......
module Gargantext.Components.Forest.Tree.Node.Action.Update where module Gargantext.Components.Forest.Tree.Node.Action.Update where
import Data.Tuple.Nested ((/\))
import Data.Maybe (Maybe(..))
import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>)) import Data.Argonaut (class EncodeJson, jsonEmptyObject, (:=), (~>))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Components.Forest.Tree.Node.Action (Action) import Gargantext.Components.Forest.Tree.Node.Action (Action)
import Gargantext.Types (NodeType) import Gargantext.Components.Forest.Tree.Node.Tools (formChoiceSafe, formButton)
import Gargantext.Types (NodeType(..))
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Prelude (Unit) import Gargantext.Prelude (Unit, class Show, class Read, show, bind, ($), pure)
import Reactix as R
import Reactix.DOM.HTML as H
{- {-
updateNode :: Session -> ID -> UpdateNodeParams -> Aff (Array ID) updateNode :: Session -> ID -> UpdateNodeParams -> Aff (Array ID)
updateNode session nodeId params = post session $ GR.NodeAPI GT.Node (Just nodeId) "" updateNode session nodeId params = post session $ GR.NodeAPI GT.Node (Just nodeId) ""
-} -}
data UpdateNodeParams = UpdateNodeParamsList { method :: Int } data UpdateNodeParams = UpdateNodeParamsList { method :: Method }
| UpdateNodeParamsGraph { method :: String } | UpdateNodeParamsGraph { method :: String }
| UpdateNodeParamsTexts { method :: Int } | UpdateNodeParamsTexts { method :: Int }
instance encodeJsonUpdateNodeParams :: EncodeJson UpdateNodeParams instance encodeJsonUpdateNodeParams :: EncodeJson UpdateNodeParams
where where
encodeJson (UpdateNodeParamsList { method }) encodeJson (UpdateNodeParamsList { method })
= "method" := method = "method" := show method
~> jsonEmptyObject ~> jsonEmptyObject
encodeJson (UpdateNodeParamsGraph { method }) encodeJson (UpdateNodeParamsGraph { method })
= "method" := method = "method" := method
...@@ -38,3 +42,32 @@ type UpdateNodeProps = ...@@ -38,3 +42,32 @@ type UpdateNodeProps =
, params :: UpdateNodeParams , params :: UpdateNodeParams
) )
----------------------------------------------------------------------
data Method = Basic | Advanced | WithModel
instance readMethod :: Read Method where
read "Basic" = Just Basic
read "Advanced" = Just Advanced
read "WithModel" = Just WithModel
read _ = Nothing
instance showMethod :: Show Method where
show Basic = "Basic"
show Advanced = "Advanced"
show WithModel = "WithModel"
----------------------------------------------------------------------
update :: NodeType -> R.Hooks R.Element
update NodeList = do
method @( _ /\ setMethod ) <- R.useState' Basic
nodeType@( _ /\ setNodeType) <- R.useState' NodeList
pure $ H.div {} [ formChoiceSafe [Basic, Advanced, WithModel] Basic setMethod
, formButton NodeList setNodeType
]
update Graph = pure $ H.div {} []
update Texts = pure $ H.div {} []
update _ = pure $ H.div {} []
-- fragmentPT $ "Update " <> show nodeType
...@@ -38,7 +38,6 @@ actionUpload _ _ _ _ = ...@@ -38,7 +38,6 @@ actionUpload _ _ _ _ =
pure $ fragmentPT $ "Soon, upload for this NodeType." pure $ fragmentPT $ "Soon, upload for this NodeType."
-- file upload types -- file upload types
data DroppedFile = data DroppedFile =
DroppedFile { contents :: UploadFileContents DroppedFile { contents :: UploadFileContents
......
...@@ -4,45 +4,32 @@ import Data.Maybe (Maybe(..)) ...@@ -4,45 +4,32 @@ import Data.Maybe (Maybe(..))
import Data.Nullable (null) import Data.Nullable (null)
import Data.String as S import Data.String as S
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (mkEffectFn1)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileContents(..))
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.CopyFrom (copyFromCorpusView) import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (copyFromCorpusView)
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.Rename (renameAction) import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction)
import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete)
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.Search.Frame (searchIframes) import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch) import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch)
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.Upload (actionUpload, DroppedFile(..), fileTypeView) import Gargantext.Components.Forest.Tree.Node.Action.Update (update)
import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload) import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload)
import Gargantext.Components.Forest.Tree.Node.Box.Types (CommonProps, NodePopupProps, NodePopupS) import Gargantext.Components.Forest.Tree.Node.Box.Types (NodePopupProps, NodePopupS)
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox) import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar (asyncProgressBar, BarType(..))
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT) import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT)
import Gargantext.Components.Forest.Tree.Node.Tools.Task (Tasks) import Gargantext.Prelude (Unit, bind, const, map, pure, show, ($), (<>), (==))
import Gargantext.Components.Forest.Tree.Node.Tools.Sync (nodeActionsGraph, nodeActionsNodeList) import Gargantext.Sessions (Session)
import Gargantext.Components.GraphExplorer.API as GraphAPI
import Gargantext.Components.Lang (Lang(EN))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, const, discard, map, pure, show, unit, void, ($), (<>), (==))
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (Name, ID) import Gargantext.Types (Name, ID)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils (glyphicon, glyphiconActive) import Gargantext.Utils (glyphicon, glyphiconActive)
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
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
import Web.File.FileReader.Aff (readAsText)
-- | START Popup View -- | START Popup View
...@@ -248,8 +235,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt ...@@ -248,8 +235,7 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
cpt {action: Add xs, dispatch, id, name, nodePopup: p, nodeType} _ = do cpt {action: Add xs, dispatch, id, name, nodePopup: p, nodeType} _ = do
pure $ addNodeView {dispatch, id, name, nodeType, nodeTypes: xs} pure $ addNodeView {dispatch, id, name, nodeType, nodeTypes: xs}
cpt {action: Refresh , dispatch, id, nodeType, session} _ = do cpt {action: Refresh , dispatch, id, nodeType, session} _ = update nodeType
pure $ fragmentPT $ "Update " <> show nodeType
cpt {action: Config , dispatch, id, nodeType, session} _ = do cpt {action: Config , dispatch, id, nodeType, session} _ = do
pure $ fragmentPT $ "Config " <> show nodeType pure $ fragmentPT $ "Config " <> show nodeType
......
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