[nlp] add languages from backend to file upload dialog

parent 719f499f
Pipeline #3901 canceled with stage
...@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search where ...@@ -3,7 +3,6 @@ module Gargantext.Components.Forest.Tree.Node.Action.Search where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Array as A import Data.Array as A
import Data.Map as Map
import Data.Maybe (Maybe) import Data.Maybe (Maybe)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
...@@ -11,7 +10,7 @@ import Gargantext.Components.App.Store (Boxes) ...@@ -11,7 +10,7 @@ import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar (searchBar) import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar (searchBar)
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.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.GraphQL.Endpoints (getLanguages) import Gargantext.Components.Forest.Tree.Node.Action.Utils (loadLanguages)
import Gargantext.Components.Lang (allLangs, Lang) import Gargantext.Components.Lang (allLangs, Lang)
import Gargantext.Config.REST (RESTError(..), AffRESTError) import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
...@@ -47,20 +46,12 @@ actionSearchCpt = here.component "actionSearch" cpt where ...@@ -47,20 +46,12 @@ actionSearchCpt = here.component "actionSearch" cpt where
actionSearchWithLangs (Record.merge props { langs }) [] } actionSearchWithLangs (Record.merge props { langs }) [] }
where where
errorHandler err = case err of errorHandler err = case err of
ReadJSONError err' -> here.warn2 "[listTreeChildren] ReadJSONError" $ show err' ReadJSONError err' -> here.warn2 "[actionSearch] ReadJSONError" $ show err'
_ -> here.warn2 "[listTreeChildren] RESTError" err _ -> here.warn2 "[actionSearch] RESTError" err
loadLanguages :: { session :: Session } -> AffRESTError (Array Lang)
loadLanguages { session } = do
eLangsMap <- getLanguages session
pure $ A.fromFoldable <$> Map.keys <$> eLangsMap
type PropsWithLangs = type PropsWithLangs =
( boxes :: Boxes ( langs :: Array Lang
, dispatch :: Action -> Aff Unit | Props )
, id :: Maybe ID
, langs :: Array Lang
, session :: Session )
-- | Action : Search -- | Action : Search
actionSearchWithLangs :: R2.Component PropsWithLangs actionSearchWithLangs :: R2.Component PropsWithLangs
......
...@@ -22,12 +22,14 @@ import Gargantext.Components.Bootstrap.Types (ComponentStatus(..)) ...@@ -22,12 +22,14 @@ import Gargantext.Components.Bootstrap.Types (ComponentStatus(..))
import Gargantext.Components.Forest.Tree.Node.Action (Props) import Gargantext.Components.Forest.Tree.Node.Action (Props)
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.Types (FileFormat(..), FileType(..), UploadFileBlob(..), readUFBAsBase64, readUFBAsText) import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileFormat(..), FileType(..), UploadFileBlob(..), readUFBAsBase64, readUFBAsText)
import Gargantext.Components.Forest.Tree.Node.Action.Utils (loadLanguages)
import Gargantext.Components.Forest.Tree.Node.Tools (fragmentPT, formChoiceSafe, panel) import Gargantext.Components.Forest.Tree.Node.Tools (fragmentPT, formChoiceSafe, panel)
import Gargantext.Components.Lang (Lang(..), langReader) import Gargantext.Components.Lang (Lang(..), langReader)
import Gargantext.Components.ListSelection as ListSelection import Gargantext.Components.ListSelection as ListSelection
import Gargantext.Components.ListSelection.Types (Selection(..)) import Gargantext.Components.ListSelection.Types (Selection(..))
import Gargantext.Components.ListSelection.Types as ListSelection import Gargantext.Components.ListSelection.Types as ListSelection
import Gargantext.Config.REST (AffRESTError, RESTError) import Gargantext.Config.REST (AffRESTError, RESTError(..))
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes as GR import Gargantext.Routes as GR
import Gargantext.Sessions (Session, postWwwUrlencoded, post) import Gargantext.Sessions (Session, postWwwUrlencoded, post)
import Gargantext.Types (ID, NodeType(..)) import Gargantext.Types (ID, NodeType(..))
...@@ -37,6 +39,7 @@ import Partial.Unsafe (unsafePartial, unsafeCrashWith) ...@@ -37,6 +39,7 @@ import Partial.Unsafe (unsafePartial, unsafeCrashWith)
import React.SyntheticEvent as E 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 Record as Record
import Toestand as T import Toestand as T
import URI.Extra.QueryPairs as QP import URI.Extra.QueryPairs as QP
import Web.File.FileReader.Aff (readAsDataURL) import Web.File.FileReader.Aff (readAsDataURL)
...@@ -103,9 +106,28 @@ type UploadFile = ...@@ -103,9 +106,28 @@ type UploadFile =
uploadFileView :: R2.Leaf Props uploadFileView :: R2.Leaf Props
uploadFileView = R2.leaf uploadFileViewCpt uploadFileView = R2.leaf uploadFileViewCpt
uploadFileViewCpt :: R.Component Props uploadFileViewCpt :: R.Component Props
uploadFileViewCpt = here.component "uploadFileView" cpt uploadFileViewCpt = here.component "uploadFileView" cpt where
cpt props@({ session }) _ = do
useLoader { errorHandler
, loader: loadLanguages
, path: { session }
, render: \langs ->
uploadFileViewWithLangs (Record.merge props { langs }) }
where where
cpt { dispatch, id, nodeType, session } _ = do errorHandler err = case err of
ReadJSONError err' -> here.warn2 "[uploadFileView] ReadJSONError" $ show err'
_ -> here.warn2 "[uploadFileView] RESTError" err
type PropsWithLangs =
( langs :: Array Lang
| Props )
uploadFileViewWithLangs :: R2.Leaf PropsWithLangs
uploadFileViewWithLangs = R2.leaf uploadFileViewWithLangsCpt
uploadFileViewWithLangsCpt :: R.Component PropsWithLangs
uploadFileViewWithLangsCpt = here.component "uploadFileViewWithLangs" cpt
where
cpt { dispatch, id, langs, nodeType, session } _ = do
-- mFile :: R.State (Maybe UploadFile) <- R.useState' Nothing -- mFile :: R.State (Maybe UploadFile) <- R.useState' Nothing
mFile <- T.useBox (Nothing :: Maybe UploadFile) mFile <- T.useBox (Nothing :: Maybe UploadFile)
fileType <- T.useBox CSV fileType <- T.useBox CSV
...@@ -147,7 +169,7 @@ uploadFileViewCpt = here.component "uploadFileView" cpt ...@@ -147,7 +169,7 @@ uploadFileViewCpt = here.component "uploadFileView" cpt
] ]
, R2.row , R2.row
[ H.div {className:"col-6 flex-space-around"} [ H.div {className:"col-6 flex-space-around"}
[ formChoiceSafe { items: [EN, FR, DE, ES, IT, PL, CN, No_extraction] [ formChoiceSafe { items: langs <> [No_extraction]
, default: EN , default: EN
, callback: setLang' , callback: setLang'
, print: show , print: show
......
module Gargantext.Components.Forest.Tree.Node.Action.Utils where
import Data.Array as A
import Data.Map as Map
import Gargantext.Components.GraphQL.Endpoints (getLanguages)
import Gargantext.Components.Lang (Lang)
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Prelude
import Gargantext.Sessions (Session)
import Gargantext.Utils.Reactix as R2
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Utils"
loadLanguages :: { session :: Session } -> AffRESTError (Array Lang)
loadLanguages { session } = do
eLangsMap <- getLanguages session
pure $ A.fromFoldable <$> Map.keys <$> eLangsMap
...@@ -98,7 +98,6 @@ type LangSwitcherProps = ( ...@@ -98,7 +98,6 @@ type LangSwitcherProps = (
langSwitcher :: R2.Component LangSwitcherProps langSwitcher :: R2.Component LangSwitcherProps
langSwitcher = R.createElement langSwitcherCpt langSwitcher = R.createElement langSwitcherCpt
langSwitcherCpt :: R.Component LangSwitcherProps langSwitcherCpt :: R.Component LangSwitcherProps
langSwitcherCpt = here.component "langSwitcher" cpt langSwitcherCpt = here.component "langSwitcher" cpt
where where
......
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