Commit 39a3fdef authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev-legacy-csv-list-upload' into 80-dev-frontend-errors

parents 1450f95f 6cfbebe7
...@@ -3,10 +3,9 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar ...@@ -3,10 +3,9 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar
, searchBar , searchBar
) where ) where
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (searchField) import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (searchField)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (Search, allDatabases)
import Gargantext.Components.Lang (Lang) import Gargantext.Components.Lang (Lang)
import Gargantext.Prelude (Unit, pure, ($)) import Gargantext.Prelude (Unit, pure, ($))
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
...@@ -35,7 +34,7 @@ searchBarCpt = here.component "searchBar" cpt ...@@ -35,7 +34,7 @@ searchBarCpt = here.component "searchBar" cpt
cpt { errors, langs, onSearch, search, session } _ = do cpt { errors, langs, onSearch, search, session } _ = do
--onSearchChange session s --onSearchChange session s
pure $ H.div { className: "search-bar" } pure $ H.div { className: "search-bar" }
[ searchField { databases:allDatabases [ searchField { databases: allDatabases
, errors , errors
, langs , langs
, onSearch , onSearch
......
...@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Upload where ...@@ -2,7 +2,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Upload where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Either (Either(..), fromRight') import Data.Either (Either, fromRight')
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..), fromJust, fromMaybe) import Data.Maybe (Maybe(..), fromJust, fromMaybe)
...@@ -320,12 +320,17 @@ uploadFile session NodeList id JSON { mName, contents } = do ...@@ -320,12 +320,17 @@ uploadFile session NodeList id JSON { mName, contents } = do
task <- post session url body task <- post session url body
pure $ GT.AsyncTaskWithType { task, typ: GT.Form } pure $ GT.AsyncTaskWithType { task, typ: GT.Form }
-} -}
uploadFile { contents, fileType: CSV, id, nodeType: NodeList, mName, session } = do
let url = GR.NodeAPI NodeList (Just id) $ GT.asyncTaskTypePath GT.ListCSVUpload
let body = [ Tuple "_wtf_data" (Just contents)
, Tuple "_wtf_filetype" (Just $ show NodeList)
, Tuple "_wtf_name" mName ]
eTask <- postWwwUrlencoded session url body
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.Form }) <$> eTask
uploadFile { contents, fileType, id, nodeType, mName, session } = do uploadFile { contents, fileType, id, nodeType, mName, session } = do
-- contents <- readAsText blob -- contents <- readAsText blob
eTask :: Either RESTError GT.AsyncTask <- postWwwUrlencoded session p bodyParams eTask :: Either RESTError GT.AsyncTask <- postWwwUrlencoded session p bodyParams
case eTask of pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.Form }) <$> eTask
Left err -> pure $ Left err
Right task -> pure $ Right $ GT.AsyncTaskWithType { task, typ: GT.Form }
--postMultipartFormData session p fileContents --postMultipartFormData session p fileContents
where where
p = case nodeType of p = case nodeType of
...@@ -333,7 +338,6 @@ uploadFile { contents, fileType, id, nodeType, mName, session } = do ...@@ -333,7 +338,6 @@ uploadFile { contents, fileType, id, nodeType, mName, session } = do
Annuaire -> GR.NodeAPI nodeType (Just id) "annuaire" Annuaire -> GR.NodeAPI nodeType (Just id) "annuaire"
NodeList -> case fileType of NodeList -> case fileType of
JSON -> GR.NodeAPI nodeType (Just id) $ GT.asyncTaskTypePath GT.ListUpload JSON -> GR.NodeAPI nodeType (Just id) $ GT.asyncTaskTypePath GT.ListUpload
CSV -> GR.NodeAPI nodeType (Just id) $ GT.asyncTaskTypePath GT.ListCSVUpload
_ -> GR.NodeAPI nodeType (Just id) "" _ -> GR.NodeAPI nodeType (Just id) ""
_ -> GR.NodeAPI nodeType (Just id) "" _ -> GR.NodeAPI nodeType (Just id) ""
......
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