Commit 38bd28e3 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[MERGE] NLP Langs

parents 8481e9f6 f82c542f
...@@ -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
......
...@@ -3,7 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Upload where ...@@ -3,7 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Action.Upload where
import Gargantext.Prelude import Gargantext.Prelude
import Affjax.RequestBody (blob) import Affjax.RequestBody (blob)
import Data.Array (singleton) import Data.Array as A
import Data.Either (Either, fromRight') import Data.Either (Either, fromRight')
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Foldable (intercalate) import Data.Foldable (intercalate)
...@@ -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
...@@ -709,11 +731,26 @@ uploadTermButtonCpt = here.component "uploadTermButton" cpt ...@@ -709,11 +731,26 @@ uploadTermButtonCpt = here.component "uploadTermButton" cpt
uploadFrameCalcView :: R2.Component Props uploadFrameCalcView :: R2.Component Props
uploadFrameCalcView = R.createElement uploadFrameCalcViewCpt uploadFrameCalcView = R.createElement uploadFrameCalcViewCpt
uploadFrameCalcViewCpt :: R.Component Props uploadFrameCalcViewCpt :: R.Component Props
uploadFrameCalcViewCpt = here.component "uploadFrameCalcView" cpt uploadFrameCalcViewCpt = here.component "uploadFrameCalcView" cpt where
cpt props@({ session }) _ = do
useLoader { errorHandler
, loader: loadLanguages
, path: { session }
, render: \langs ->
uploadFileViewWithLangs (Record.merge props { langs }) }
where where
cpt { dispatch, session } _ = do errorHandler err = case err of
ReadJSONError err' -> here.warn2 "[uploadFileView] ReadJSONError" $ show err'
_ -> here.warn2 "[uploadFileView] RESTError" err
uploadFrameCalcViewWithLangs :: R2.Component PropsWithLangs
uploadFrameCalcViewWithLangs = R.createElement uploadFrameCalcViewWithLangsCpt
uploadFrameCalcViewWithLangsCpt :: R.Component PropsWithLangs
uploadFrameCalcViewWithLangsCpt = here.component "uploadFrameCalcViewWithLangs" cpt
where
cpt { dispatch, langs, session } _ = do
lang' /\ langBox lang' /\ langBox
<- R2.useBox' EN <- R2.useBox' $ fromMaybe Universal $ A.head langs
selection' /\ selectionBox selection' /\ selectionBox
<- R2.useBox' ListSelection.MyListsFirst <- R2.useBox' ListSelection.MyListsFirst
...@@ -741,7 +778,7 @@ uploadFrameCalcViewCpt = here.component "uploadFrameCalcView" cpt ...@@ -741,7 +778,7 @@ uploadFrameCalcViewCpt = here.component "uploadFrameCalcView" cpt
B.formSelect' B.formSelect'
{ callback: flip T.write_ langBox { callback: flip T.write_ langBox
, value: lang' , value: lang'
, list: [ EN, FR, No_extraction, Universal ] , list: langs <> [ No_extraction, Universal ]
} }
[] []
] ]
......
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.sort <$> A.fromFoldable <$> Map.keys <$> eLangsMap
...@@ -2,24 +2,28 @@ module Gargantext.Components.Forest.Tree.Node.Action.WriteNodesDocuments where ...@@ -2,24 +2,28 @@ module Gargantext.Components.Forest.Tree.Node.Action.WriteNodesDocuments where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Array as A
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..), fromMaybe)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
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.Utils (loadLanguages)
import Gargantext.Components.Forest.Tree.Node.Tools (panel, submitButton) import Gargantext.Components.Forest.Tree.Node.Tools (panel, submitButton)
import Gargantext.Components.Lang (Lang(..)) import Gargantext.Components.Lang (Lang(..))
import Gargantext.Components.ListSelection as ListSelection import Gargantext.Components.ListSelection as ListSelection
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 (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, post) import Gargantext.Sessions (Session, post)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
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
...@@ -37,10 +41,29 @@ actionWriteNodesDocuments :: R2.Component ActionWriteNodesDocuments ...@@ -37,10 +41,29 @@ actionWriteNodesDocuments :: R2.Component ActionWriteNodesDocuments
actionWriteNodesDocuments = R.createElement actionWriteNodesDocumentsCpt actionWriteNodesDocuments = R.createElement actionWriteNodesDocumentsCpt
actionWriteNodesDocumentsCpt :: R.Component ActionWriteNodesDocuments actionWriteNodesDocumentsCpt :: R.Component ActionWriteNodesDocuments
actionWriteNodesDocumentsCpt = here.component "actionWriteNodesDocuments" cpt where actionWriteNodesDocumentsCpt = here.component "actionWriteNodesDocuments" cpt where
cpt { boxes, dispatch, id, session } _ = do cpt props@({ session }) _ = do
useLoader { errorHandler
, loader: loadLanguages
, path: { session }
, render: \langs ->
actionWriteNodesDocumentsWithLangs (Record.merge props { langs }) [] }
where
errorHandler err = case err of
ReadJSONError err' -> here.warn2 "[actionSearch] ReadJSONError" $ show err'
_ -> here.warn2 "[actionSearch] RESTError" err
type ActionWriteNodesDocumentsWithLangs =
( langs :: Array Lang
| ActionWriteNodesDocuments )
actionWriteNodesDocumentsWithLangs :: R2.Component ActionWriteNodesDocumentsWithLangs
actionWriteNodesDocumentsWithLangs = R.createElement actionWriteNodesDocumentsWithLangsCpt
actionWriteNodesDocumentsWithLangsCpt :: R.Component ActionWriteNodesDocumentsWithLangs
actionWriteNodesDocumentsWithLangsCpt = here.component "actionWriteNodesDocumentsWithLangs" cpt where
cpt { dispatch, id, langs, session } _ = do
lang' /\ langBox lang' /\ langBox
<- R2.useBox' EN <- R2.useBox' $ fromMaybe Universal $ A.head langs
selection' /\ selectionBox selection' /\ selectionBox
<- R2.useBox' ListSelection.MyListsFirst <- R2.useBox' ListSelection.MyListsFirst
paragraphs' /\ paragraphBox paragraphs' /\ paragraphBox
...@@ -70,7 +93,7 @@ actionWriteNodesDocumentsCpt = here.component "actionWriteNodesDocuments" cpt wh ...@@ -70,7 +93,7 @@ actionWriteNodesDocumentsCpt = here.component "actionWriteNodesDocuments" cpt wh
B.formSelect' B.formSelect'
{ callback: flip T.write_ langBox { callback: flip T.write_ langBox
, value: lang' , value: lang'
, list: [ EN, FR, No_extraction, Universal ] , list: langs <> [ No_extraction, Universal ]
} }
[] []
] ]
......
...@@ -34,7 +34,7 @@ allLangs = [ EN ...@@ -34,7 +34,7 @@ allLangs = [ EN
, No_extraction , No_extraction
] ]
data Lang = FR | EN | DE | ES | IT | PL | CN | Universal | No_extraction data Lang = CN | DE | EN | ES | FR | IT | PL | Universal | No_extraction
derive instance Generic Lang _ derive instance Generic Lang _
derive instance Ord Lang derive instance Ord Lang
...@@ -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