Commit 6563ea3f authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT|Tree/Action] split upload

parent c7ebcbab
......@@ -3,21 +3,19 @@ module Gargantext.Components.Forest where
import Gargantext.Prelude
import Data.Array as A
import Data.Map as Map
import Data.Maybe (Maybe(..))
import Data.Set as Set
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree (treeView)
import Gargantext.Components.Forest.Tree.Node.Action (Reload)
import Gargantext.Ends (Frontends)
import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session(..), Sessions, OpenNodes, unSessions)
import Gargantext.Types (Reload)
import Gargantext.Utils.Reactix as R2
type Props =
......
......@@ -16,16 +16,20 @@ import Record as Record
import Record.Extra as RecordE
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), FTree, ID, LNode(..), NTree(..), Reload, RenameValue(..), Tree, deleteNode, loadNode, renameNode)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..),deleteNode)
import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (loadNode)
import Gargantext.Components.Forest.Tree.Node.Action.Add (AddNodeValue(..), addNode)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (RenameValue(..), renameNode)
import Gargantext.Components.Forest.Tree.Node.Box (nodeMainSpan, Tasks, tasksStruct)
import Gargantext.Components.Forest.Tree.Node.FTree (FTree, LNode(..), NTree(..), Tree)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, const, discard, map, pure, void, ($), (+), (/=), (<>), identity)
import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (OpenNodes, Session, mkNodeId)
import Gargantext.Types as GT
import Gargantext.Types (ID, Reload)
------------------------------------------------------------------------
......
......@@ -28,3 +28,25 @@ data Action = CreateSubmit String GT.NodeType
deleteNode :: Session -> GT.ID -> Aff GT.ID
deleteNode session nodeId = delete session $ NodeAPI GT.Node (Just nodeId) ""
-----------------------------------------------------------------------
type Props =
( dispatch :: Action -> Aff Unit
, id :: Int
, nodeType :: GT.NodeType
, session :: Session
)
-- TODO remove these types from here
data FileType = CSV | CSV_HAL | WOS | PresseRIS
derive instance genericFileType :: Generic FileType _
instance eqFileType :: Eq FileType where
eq = genericEq
instance showFileType :: Show FileType where
show = genericShow
newtype UploadFileContents = UploadFileContents String
......@@ -7,7 +7,7 @@ import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff)
import Effect.Uncurried (mkEffectFn1)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), ID, Name)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node (SettingsBox(..), settingsBox)
import Gargantext.Types (NodeType(..), readNodeType)
import Gargantext.Utils.Reactix as R2
......@@ -19,11 +19,11 @@ import Reactix as R
import Reactix.DOM.HTML as H
----------------------------------------------------------------------
addNode :: Session -> ID -> AddNodeValue -> Aff (Array ID)
addNode :: Session -> GT.ID -> AddNodeValue -> Aff (Array GT.ID)
addNode session parentId = post session $ GR.NodeAPI GT.Node (Just parentId) ""
addNodeAsync :: Session
-> ID
-> GT.ID
-> AddNodeValue
-> Aff GT.AsyncTaskWithType
addNodeAsync session parentId q = do
......@@ -35,7 +35,7 @@ addNodeAsync session parentId q = do
----------------------------------------------------------------------
-- TODO AddNodeParams
newtype AddNodeValue = AddNodeValue
{ name :: Name
{ name :: GT.Name
, nodeType :: GT.NodeType
}
......@@ -49,9 +49,9 @@ instance encodeJsonAddNodeValue :: EncodeJson AddNodeValue where
data NodePopup = CreatePopup | NodePopup
type CreateNodeProps =
( id :: ID
( id :: GT.ID
, dispatch :: Action -> Aff Unit
, name :: Name
, name :: GT.Name
, nodeType :: NodeType
, nodeTypes :: Array NodeType
)
......
......@@ -19,7 +19,7 @@ import Web.File.FileReader.Aff (readAsText)
import Gargantext.Prelude (class Show, Unit, bind, const, discard, map, pure, show, unit, void, ($), (&&), (/=), (<>))
import Gargantext.Components.Lang (readLang, Lang(..))
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), Props)
import Gargantext.Components.Forest.Tree.Node.FTree (FTree, ID, LNode(..), NTree(..))
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR
......@@ -30,7 +30,7 @@ import Gargantext.Utils.Reactix as R2
loadNode :: Session -> GT.ID -> Aff FTree
loadNode session nodeId = get session $ NodeAPI GT.Tree (Just nodeId) ""
loadNode session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
copyFromCorpusView :: Record Props -> R.Element
copyFromCorpusView props = R.createElement copyFromCorpusViewCpt props []
......
module Gargantext.Components.Forest.Tree.Node.Action.Rename where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff)
import Effect.Uncurried (mkEffectFn1)
......@@ -8,13 +10,16 @@ import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Types (NodeType)
import Gargantext.Types as GT
import Gargantext.Types (NodeType, ID, Name)
import Gargantext.Routes as GR
import Gargantext.Utils.Reactix as R2
import Gargantext.Sessions (Session, get, put, post, delete)
renameNode :: Session -> ID -> RenameValue -> Aff (Array ID)
renameNode session renameNodeId =
put session $ NodeAPI GT.Node (Just renameNodeId) "rename"
put session $ GR.NodeAPI GT.Node (Just renameNodeId) "rename"
newtype RenameValue = RenameValue
{ name :: Name }
......
......@@ -7,7 +7,7 @@ import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff)
import Effect.Uncurried (mkEffectFn1)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), ID, Name)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node (SettingsBox(..), settingsBox)
import Gargantext.Types (NodeType(..), readNodeType)
import Gargantext.Utils.Reactix as R2
......@@ -41,9 +41,9 @@ instance encodeJsonUpdateNodeParams :: EncodeJson UpdateNodeParams
----------------------------------------------------------------------
type UpdateNodeProps =
( id :: ID
( id :: GT.ID
, dispatch :: Action -> Aff Unit
, name :: Name
, name :: GT.Name
, nodeType :: NodeType
, params :: UpdateNodeParams
)
......
......@@ -19,7 +19,7 @@ import Web.File.FileReader.Aff (readAsText)
import Gargantext.Prelude (class Show, Unit, bind, const, discard, map, pure, show, unit, void, ($), (&&), (/=), (<>))
import Gargantext.Components.Lang (readLang, Lang(..))
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), Props, FileType(..), UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.FTree (FTree, ID, LNode(..), NTree(..))
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR
......@@ -30,23 +30,6 @@ import Gargantext.Utils.Reactix as R2
-- UploadFile Action
-- file upload types
data FileType = CSV | CSV_HAL | WOS | PresseRIS
derive instance genericFileType :: Generic FileType _
instance eqFileType :: Eq FileType where
eq = genericEq
instance showFileType :: Show FileType where
show = genericShow
readFileType :: String -> Maybe FileType
readFileType "CSV" = Just CSV
readFileType "CSV_HAL" = Just CSV_HAL
readFileType "PresseRIS" = Just PresseRIS
readFileType "WOS" = Just WOS
readFileType _ = Nothing
data DroppedFile =
DroppedFile { contents :: UploadFileContents
, fileType :: Maybe FileType
......@@ -55,18 +38,12 @@ data DroppedFile =
type FileHash = String
newtype UploadFileContents = UploadFileContents String
type UploadFile =
{ contents :: UploadFileContents
, name :: String
}
type Props =
( dispatch :: Action -> Aff Unit
, id :: Int
, nodeType :: GT.NodeType
, session :: Session
)
uploadFileView :: Record Props -> R.Element
uploadFileView props = R.createElement uploadFileViewCpt props []
......@@ -141,7 +118,7 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
type UploadButtonProps =
( dispatch :: Dispatch
( dispatch :: Action -> Aff Unit
, fileType :: R.State FileType
, id :: GT.ID
, lang :: R.State (Maybe Lang)
......@@ -173,7 +150,7 @@ uploadButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.uploadButton" cpt
-- START File Type View
type FileTypeProps =
( dispatch :: Dispatch
( dispatch :: Action -> Aff Unit
, droppedFile :: R.State (Maybe DroppedFile)
, id :: ID
, isDragOver :: R.State Boolean
......@@ -315,7 +292,7 @@ uploadTermListViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadTermListView" cpt
type UploadTermButtonProps =
( dispatch :: Dispatch
( dispatch :: Action -> Aff Unit
, id :: Int
, mFile :: R.State (Maybe UploadFile)
, nodeType :: GT.NodeType
......@@ -341,3 +318,14 @@ uploadTermButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.uploadTermButton" cpt
liftEffect $ do
setMFile $ const $ Nothing
-- | UTils
readFileType :: String -> Maybe FileType
readFileType "CSV" = Just CSV
readFileType "CSV_HAL" = Just CSV_HAL
readFileType "PresseRIS" = Just PresseRIS
readFileType "WOS" = Just WOS
readFileType _ = Nothing
......@@ -27,11 +27,12 @@ import Gargantext.Prelude
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), DroppedFile(..), FileType(..), ID, Name, Reload, UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), FileType(..), UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), addNodeView)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameBox)
import Gargantext.Components.Forest.Tree.Node.Action.Update
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFileView, fileTypeView, uploadTermListView, copyFromCorpusView)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (DroppedFile(..), uploadFileView, fileTypeView, uploadTermListView)
import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (copyFromCorpusView)
import Gargantext.Components.Forest.Tree.Node.ProgressBar (asyncProgressBar, BarType(..))
import Gargantext.Components.GraphExplorer.API as GraphAPI
import Gargantext.Components.Lang (allLangs, Lang(EN))
......@@ -44,7 +45,7 @@ import Gargantext.Ends (Frontends, url)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as Routes
import Gargantext.Sessions (Session, sessionId, post)
import Gargantext.Types (NodeType(..))
import Gargantext.Types (NodeType(..), ID, Name, Reload)
import Gargantext.Types as GT
import Gargantext.Utils (glyphicon, glyphiconActive)
import Gargantext.Utils.Popover as Popover
......
......@@ -9,7 +9,6 @@ import Effect (Effect)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)
import Effect.Timer (clearInterval, setInterval)
import Gargantext.Components.Forest.Tree.Node.Action (ID)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types as GT
......@@ -26,7 +25,7 @@ type Props =
(
asyncTask :: GT.AsyncTaskWithType
, barType :: BarType
, corpusId :: ID
, corpusId :: GT.ID
, onFinish :: Unit -> Effect Unit
, session :: Session
)
......
......@@ -15,8 +15,9 @@ import Effect.Aff (Aff)
import Prim.Row (class Union)
import URI.Query (Query)
type ID = Int
type Name = String
type ID = Int
type Name = String
type Reload = Int
newtype SessionId = SessionId String
type NodeID = Int
......
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