]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/Corpus/Annuaire.hs
[API] simulate logs and update async api ok
[gargantext.git] / src / Gargantext / API / Node / Corpus / Annuaire.hs
1 {-|
2 Module : Gargantext.API.Node.Corpus.Annuaire
3 Description : New annuaire API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9 -}
10
11 {-# LANGUAGE TemplateHaskell #-}
12 {-# LANGUAGE TypeOperators #-}
13
14 module Gargantext.API.Node.Corpus.Annuaire
15 where
16
17 import Control.Lens hiding (elements)
18 import Data.Aeson
19 import Data.Swagger
20 import Data.Text (Text)
21 import GHC.Generics (Generic)
22 import Gargantext.API.Admin.Orchestrator.Types
23 import Gargantext.Core (Lang(..))
24 import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
25 import Gargantext.Database.Action.Flow (FlowCmdM) -- flowAnnuaire
26 import Gargantext.Database.Admin.Types.Node (AnnuaireId)
27 import Gargantext.Prelude
28 import Servant
29 import Servant.Job.Core
30 import Servant.Job.Types
31 import Servant.Job.Utils (jsonOptions)
32 import Web.FormUrlEncoded (FromForm)
33 import qualified Gargantext.API.Node.Corpus.New.File as NewFile
34
35
36 type Api = Summary "New Annuaire endpoint"
37 :> Post '[JSON] AnnuaireId
38
39 ------------------------------------------------------------------------
40 ------------------------------------------------------------------------
41 data AnnuaireWithForm = AnnuaireWithForm
42 { _wf_filetype :: !NewFile.FileType
43 , _wf_data :: !Text
44 , _wf_lang :: !(Maybe Lang)
45 } deriving (Eq, Show, Generic)
46
47 makeLenses ''AnnuaireWithForm
48 instance FromForm AnnuaireWithForm
49 instance FromJSON AnnuaireWithForm where
50 parseJSON = genericParseJSON $ jsonOptions "_wf_"
51 instance ToSchema AnnuaireWithForm where
52 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
53
54 ------------------------------------------------------------------------
55 type AsyncJobs event ctI input output =
56 AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output
57 ------------------------------------------------------------------------
58
59 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
60 :> "annuaire"
61 :> Capture "annuaire_id" AnnuaireId
62 :> "add"
63 :> "form"
64 :> "async"
65 :> AsyncJobs ScraperStatus '[FormUrlEncoded] AnnuaireWithForm ScraperStatus
66
67 ------------------------------------------------------------------------
68 addToAnnuaireWithForm :: FlowCmdM env err m
69 => AnnuaireId
70 -> AnnuaireWithForm
71 -> (ScraperStatus -> m ())
72 -> m ScraperStatus
73 addToAnnuaireWithForm _cid (AnnuaireWithForm ft _d _l) logStatus = do
74
75 printDebug "ft" ft
76
77 -- let
78 -- parse = case ft of
79 -- CSV_HAL -> Parser.parseFormat Parser.CsvHal
80 -- CSV -> Parser.parseFormat Parser.CsvGargV3
81 -- WOS -> Parser.parseFormat Parser.WOS
82 -- PresseRIS -> Parser.parseFormat Parser.RisPresse
83
84 -- docs <- liftBase
85 -- $ splitEvery 500
86 -- <$> take 1000000
87 -- <$> parse (cs d)
88
89 logStatus ScraperStatus { _scst_succeeded = Just 1
90 , _scst_failed = Just 0
91 , _scst_remaining = Just 1
92 , _scst_events = Just []
93 }
94 -- cid' <- flowCorpus "user1"
95 -- (Right [cid])
96 -- (Multi $ fromMaybe EN l)
97 -- (map (map toHyperdataDocument) docs)
98
99 -- printDebug "cid'" cid'
100
101 pure ScraperStatus { _scst_succeeded = Just 2
102 , _scst_failed = Just 0
103 , _scst_remaining = Just 0
104 , _scst_events = Just []
105 }
106