Commit 5815ecba authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] using fromChoiceSafe

parent bced885a
...@@ -87,7 +87,6 @@ addNodeView p@{ dispatch, nodeType, nodeTypes } = R.createElement el p [] ...@@ -87,7 +87,6 @@ addNodeView p@{ dispatch, nodeType, nodeTypes } = R.createElement el p []
] ]
-- END Create Node -- END Create Node
showConfig :: NodeType -> R.Element showConfig :: NodeType -> R.Element
......
module Gargantext.Components.Forest.Tree.Node.Action.Upload where module Gargantext.Components.Forest.Tree.Node.Action.Upload where
import Data.Maybe (Maybe(..), fromJust) import Data.Maybe (Maybe(..), fromJust, fromMaybe)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
...@@ -9,7 +9,7 @@ import Effect.Aff (Aff, launchAff) ...@@ -9,7 +9,7 @@ import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), Props) import Gargantext.Components.Forest.Tree.Node.Action (Action(..), Props)
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.Tools (fragmentPT) import Gargantext.Components.Forest.Tree.Node.Tools (fragmentPT, formChoiceSafe)
import Gargantext.Components.Lang (Lang(..)) import Gargantext.Components.Lang (Lang(..))
import Gargantext.Prelude (class Show, Unit, discard, bind, const, id, map, pure, show, unit, void, ($), read) import Gargantext.Prelude (class Show, Unit, discard, bind, const, id, map, pure, show, unit, void, ($), read)
import Gargantext.Routes as GR import Gargantext.Routes as GR
...@@ -43,7 +43,7 @@ actionUpload _ _ _ _ = ...@@ -43,7 +43,7 @@ actionUpload _ _ _ _ =
data DroppedFile = data DroppedFile =
DroppedFile { contents :: UploadFileContents DroppedFile { contents :: UploadFileContents
, fileType :: Maybe FileType , fileType :: Maybe FileType
, lang :: Maybe Lang , lang :: Lang
} }
type FileHash = String type FileHash = String
...@@ -63,8 +63,8 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt ...@@ -63,8 +63,8 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
where where
cpt {dispatch, id, nodeType} _ = do cpt {dispatch, id, nodeType} _ = do
mFile :: R.State (Maybe UploadFile) <- R.useState' Nothing mFile :: R.State (Maybe UploadFile) <- R.useState' Nothing
fileType :: R.State FileType <- R.useState' CSV fileType@(_ /\ setFileType) <- R.useState' CSV
lang :: R.State (Maybe Lang) <- R.useState' (Just EN) lang@( _chosenLang /\ setLang) <- R.useState' EN
pure $ pure $
H.div {className:""} H.div {className:""}
...@@ -76,21 +76,15 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt ...@@ -76,21 +76,15 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
} }
] ]
, H.div {className:"col-md-3 flex-space-around"} , H.div {className:"col-md-3 flex-space-around"}
[ R2.select {className: "form-control" [ formChoiceSafe [ CSV
, on: {change: onChangeFileType fileType} , CSV_HAL
} , WOS
( map renderOptionFT [ CSV , PresseRIS
, CSV_HAL ] CSV setFileType
, WOS
, PresseRIS
]
)
] ]
, H.div {className:"col-md-3 flex-space-around"} , H.div {className:"col-md-3 flex-space-around"}
[ R2.select { className: "form-control" [ formChoiceSafe [EN, FR, No_extraction, Universal] EN setLang ]
, on: {change: onChangeLang lang}
} (map renderOptionLang [EN, FR])
]
] ]
, H.div { className : "panel-footer" } , H.div { className : "panel-footer" }
...@@ -102,7 +96,7 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt ...@@ -102,7 +96,7 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
, id , id
, mFile , mFile
, nodeType , nodeType
} }
] ]
] ]
] ]
...@@ -136,22 +130,12 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt ...@@ -136,22 +130,12 @@ uploadFileViewCpt = R.hooksComponent "G.C.F.T.N.A.U.UploadFileView" cpt
$ read $ read
$ R2.unsafeEventValue e $ R2.unsafeEventValue e
onChangeLang :: forall e
. R.State (Maybe Lang)
-> e
-> Effect Unit
onChangeLang (lang /\ setLang) e = do
setLang $ const
$ unsafePartial
$ read
$ R2.unsafeEventValue e
type UploadButtonProps = type UploadButtonProps =
( dispatch :: Action -> Aff Unit ( dispatch :: Action -> Aff Unit
, fileType :: R.State FileType , fileType :: R.State FileType
, id :: GT.ID , id :: GT.ID
, lang :: R.State (Maybe Lang) , lang :: R.State Lang
, mFile :: R.State (Maybe UploadFile) , mFile :: R.State (Maybe UploadFile)
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
) )
...@@ -187,7 +171,7 @@ uploadButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.uploadButton" cpt ...@@ -187,7 +171,7 @@ uploadButtonCpt = R.hooksComponent "G.C.F.T.N.A.U.uploadButton" cpt
liftEffect $ do liftEffect $ do
setMFile $ const $ Nothing setMFile $ const $ Nothing
setFileType $ const $ CSV setFileType $ const $ CSV
setLang $ const $ Just EN setLang $ const $ EN
-- START File Type View -- START File Type View
type FileTypeProps = type FileTypeProps =
...@@ -250,7 +234,7 @@ fileTypeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.fileTypeView" cpt ...@@ -250,7 +234,7 @@ fileTypeViewCpt = R.hooksComponent "G.C.F.T.N.A.U.fileTypeView" cpt
onChange e l = onChange e l =
setDroppedFile $ const $ Just $ DroppedFile $ { contents setDroppedFile $ const $ Just $ DroppedFile $ { contents
, fileType: read $ R2.unsafeEventValue e , fileType: read $ R2.unsafeEventValue e
, lang : read $ R2.unsafeEventValue l , lang : fromMaybe EN $ read $ R2.unsafeEventValue l
} }
renderOption opt = H.option {} [ H.text $ show opt ] renderOption opt = H.option {} [ H.text $ show opt ]
......
...@@ -146,7 +146,7 @@ nodeMainSpan p@{ dispatch, folderOpen, frontends, session } = R.createElement el ...@@ -146,7 +146,7 @@ nodeMainSpan p@{ dispatch, folderOpen, frontends, session } = R.createElement el
$ Just $ Just
$ DroppedFile { contents: (UploadFileContents contents) $ DroppedFile { contents: (UploadFileContents contents)
, fileType: Just CSV , fileType: Just CSV
, lang : Just EN , lang : EN
} }
onDragOverHandler (_ /\ setIsDragOver) e = do onDragOverHandler (_ /\ setIsDragOver) e = do
-- prevent redirection when file is dropped -- prevent redirection when file is dropped
......
...@@ -15,9 +15,9 @@ allLangs = [ EN ...@@ -15,9 +15,9 @@ allLangs = [ EN
data Lang = FR | EN | Universal | No_extraction data Lang = FR | EN | Universal | No_extraction
instance showLang :: Show Lang where instance showLang :: Show Lang where
show FR = "FR" show FR = "FR"
show EN = "EN" show EN = "EN"
show Universal = "All" show Universal = "All"
show No_extraction = "Nothing" show No_extraction = "Nothing"
derive instance eqLang :: Eq Lang derive instance eqLang :: Eq Lang
...@@ -33,6 +33,5 @@ instance readLang :: Read Lang where ...@@ -33,6 +33,5 @@ instance readLang :: Read Lang where
instance encodeJsonLang :: EncodeJson Lang where instance encodeJsonLang :: EncodeJson Lang where
encodeJson a = encodeJson (show a) encodeJson a = encodeJson (show a)
-- Language used for the landing page -- Language used for the landing page
data LandingLang = LL_EN | LL_FR data LandingLang = LL_EN | LL_FR
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