Commit 5722575b authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Lang to upload + instances

parent 5da469ed
Pipeline #4660 canceled with stage
...@@ -29,6 +29,7 @@ import Control.Lens hiding (elements) ...@@ -29,6 +29,7 @@ import Control.Lens hiding (elements)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Data.Aeson import Data.Aeson
import Data.Aeson.TH (deriveJSON) import Data.Aeson.TH (deriveJSON)
import Data.Maybe (fromMaybe)
import Data.Either import Data.Either
import Data.Swagger import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
...@@ -43,7 +44,7 @@ import Gargantext.Database.Types.Node (CorpusId) ...@@ -43,7 +44,7 @@ import Gargantext.Database.Types.Node (CorpusId)
import Gargantext.Database.Types.Node (ToHyperdataDocument(..)) import Gargantext.Database.Types.Node (ToHyperdataDocument(..))
import Gargantext.Database.Types.Node (UserId) import Gargantext.Database.Types.Node (UserId)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Text.Corpus.Parsers (FileFormat(..), parseFormat) import qualified Gargantext.Text.Corpus.Parsers as Parser (FileFormat(..), parseFormat)
import Gargantext.Text.Terms (TermType(..)) import Gargantext.Text.Terms (TermType(..))
import Servant import Servant
import Servant.API.Flatten (Flat) import Servant.API.Flatten (Flat)
...@@ -127,6 +128,7 @@ instance ToSchema WithQuery where ...@@ -127,6 +128,7 @@ instance ToSchema WithQuery where
data WithForm = WithForm data WithForm = WithForm
{ _wf_filetype :: !FileType { _wf_filetype :: !FileType
, _wf_data :: !Text , _wf_data :: !Text
, _wf_lang :: !(Maybe Lang)
} deriving (Eq, Show, Generic) } deriving (Eq, Show, Generic)
makeLenses ''WithForm makeLenses ''WithForm
...@@ -221,15 +223,16 @@ addToCorpusWithForm :: FlowCmdM env err m ...@@ -221,15 +223,16 @@ addToCorpusWithForm :: FlowCmdM env err m
-> WithForm -> WithForm
-> (ScraperStatus -> m ()) -> (ScraperStatus -> m ())
-> m ScraperStatus -> m ScraperStatus
addToCorpusWithForm cid (WithForm ft d) logStatus = do addToCorpusWithForm cid (WithForm ft d l) logStatus = do
printDebug "ft" ft printDebug "ft" ft
let let
parse = case ft of parse = case ft of
CSV_HAL -> parseFormat CsvHal CSV_HAL -> Parser.parseFormat Parser.CsvHal
CSV -> parseFormat CsvGargV3 CSV -> Parser.parseFormat Parser.CsvGargV3
_ -> parseFormat CsvHal WOS -> Parser.parseFormat Parser.WOS
PresseRIS -> Parser.parseFormat Parser.RisPresse
docs <- liftIO docs <- liftIO
$ splitEvery 500 $ splitEvery 500
...@@ -241,8 +244,11 @@ addToCorpusWithForm cid (WithForm ft d) logStatus = do ...@@ -241,8 +244,11 @@ addToCorpusWithForm cid (WithForm ft d) logStatus = do
, _scst_remaining = Just 1 , _scst_remaining = Just 1
, _scst_events = Just [] , _scst_events = Just []
} }
cid' <- flowCorpus "user1"
(Right [cid])
(Multi $ fromMaybe EN l)
(map (map toHyperdataDocument) docs)
cid' <- flowCorpus "user1" (Right [cid]) (Multi EN) (map (map toHyperdataDocument) docs)
printDebug "cid'" cid' printDebug "cid'" cid'
pure ScraperStatus { _scst_succeeded = Just 2 pure ScraperStatus { _scst_succeeded = Just 2
......
...@@ -48,7 +48,10 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) ...@@ -48,7 +48,10 @@ import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------- -------------------------------------------------------------
type Hash = Text type Hash = Text
data FileType = CSV | CSV_HAL | PresseRIS data FileType = CSV
| CSV_HAL
| PresseRIS
| WOS
deriving (Eq, Show, Generic) deriving (Eq, Show, Generic)
instance ToSchema FileType instance ToSchema FileType
......
...@@ -12,6 +12,7 @@ Portability : POSIX ...@@ -12,6 +12,7 @@ Portability : POSIX
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module Gargantext.Core module Gargantext.Core
where where
...@@ -19,7 +20,9 @@ module Gargantext.Core ...@@ -19,7 +20,9 @@ module Gargantext.Core
import Gargantext.Prelude import Gargantext.Prelude
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Data.Aeson import Data.Aeson
import Data.Either(Either(Left))
import Data.Swagger import Data.Swagger
import Servant.API
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | Language of a Text -- | Language of a Text
-- For simplicity, we suppose text has an homogenous language -- For simplicity, we suppose text has an homogenous language
...@@ -42,6 +45,11 @@ data Lang = EN | FR | All ...@@ -42,6 +45,11 @@ data Lang = EN | FR | All
instance ToJSON Lang instance ToJSON Lang
instance FromJSON Lang instance FromJSON Lang
instance ToSchema Lang instance ToSchema Lang
instance FromHttpApiData Lang
where
parseUrlPiece "EN" = pure EN
parseUrlPiece "FR" = pure FR
parseUrlPiece "All" = pure All
parseUrlPiece _ = Left "Unexpected value of OrderBy"
allLangs :: [Lang] allLangs :: [Lang]
allLangs = [minBound ..] allLangs = [minBound ..]
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