2 Module : Gargantext.API.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
11 {-# LANGUAGE NoImplicitPrelude #-}
12 {-# LANGUAGE TemplateHaskell #-}
13 {-# LANGUAGE DeriveGeneric #-}
14 {-# LANGUAGE DataKinds #-}
15 {-# LANGUAGE TypeOperators #-}
16 {-# LANGUAGE OverloadedStrings #-}
17 {-# LANGUAGE FlexibleContexts #-}
18 {-# LANGUAGE RankNTypes #-}
20 module Gargantext.API.Annuaire
23 import Control.Lens hiding (elements)
26 import Data.Text (Text)
27 import GHC.Generics (Generic)
28 import qualified Gargantext.API.Corpus.New.File as NewFile
29 import Gargantext.API.Orchestrator.Types
30 import Gargantext.Core (Lang(..))
31 import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
32 import Gargantext.Database.Flow (FlowCmdM) -- flowAnnuaire
33 import Gargantext.Database.Types.Node (AnnuaireId)
34 import Gargantext.Prelude
36 import Servant.API.Flatten (Flat)
37 import Servant.Job.Core
38 import Servant.Job.Types
39 import Servant.Job.Utils (jsonOptions)
40 import Web.FormUrlEncoded (FromForm)
43 type Api = Summary "New Annuaire endpoint"
44 :> Post '[JSON] AnnuaireId
46 ------------------------------------------------------------------------
47 ------------------------------------------------------------------------
48 data WithForm = WithForm
49 { _wf_filetype :: !NewFile.FileType
51 , _wf_lang :: !(Maybe Lang)
52 } deriving (Eq, Show, Generic)
55 instance FromForm WithForm
56 instance FromJSON WithForm where
57 parseJSON = genericParseJSON $ jsonOptions "_wf_"
58 instance ToSchema WithForm where
59 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
61 ------------------------------------------------------------------------
62 type AsyncJobs event ctI input output =
63 Flat (AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output)
64 ------------------------------------------------------------------------
66 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
68 :> Capture "annuaire_id" AnnuaireId
72 :> AsyncJobs ScraperStatus '[FormUrlEncoded] WithForm ScraperStatus
74 ------------------------------------------------------------------------
75 addToAnnuaireWithForm :: FlowCmdM env err m
78 -> (ScraperStatus -> m ())
80 addToAnnuaireWithForm _cid (WithForm ft _d _l) logStatus = do
86 -- CSV_HAL -> Parser.parseFormat Parser.CsvHal
87 -- CSV -> Parser.parseFormat Parser.CsvGargV3
88 -- WOS -> Parser.parseFormat Parser.WOS
89 -- PresseRIS -> Parser.parseFormat Parser.RisPresse
96 logStatus ScraperStatus { _scst_succeeded = Just 1
97 , _scst_failed = Just 0
98 , _scst_remaining = Just 1
99 , _scst_events = Just []
101 -- cid' <- flowCorpus "user1"
103 -- (Multi $ fromMaybe EN l)
104 -- (map (map toHyperdataDocument) docs)
106 -- printDebug "cid'" cid'
108 pure ScraperStatus { _scst_succeeded = Just 2
109 , _scst_failed = Just 0
110 , _scst_remaining = Just 0
111 , _scst_events = Just []