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
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.Node.Corpus.Annuaire
23 import Control.Lens hiding (elements)
26 import Data.Text (Text)
27 import GHC.Generics (Generic)
28 import Gargantext.API.Admin.Orchestrator.Types
29 import Gargantext.Core (Lang(..))
30 import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
31 import Gargantext.Database.Action.Flow (FlowCmdM) -- flowAnnuaire
32 import Gargantext.Database.Admin.Types.Node (AnnuaireId)
33 import Gargantext.Prelude
35 import Servant.Job.Core
36 import Servant.Job.Types
37 import Servant.Job.Utils (jsonOptions)
38 import Web.FormUrlEncoded (FromForm)
39 import qualified Gargantext.API.Node.Corpus.New.File as NewFile
42 type Api = Summary "New Annuaire endpoint"
43 :> Post '[JSON] AnnuaireId
45 ------------------------------------------------------------------------
46 ------------------------------------------------------------------------
47 data WithForm = WithForm
48 { _wf_filetype :: !NewFile.FileType
50 , _wf_lang :: !(Maybe Lang)
51 } deriving (Eq, Show, Generic)
54 instance FromForm WithForm
55 instance FromJSON WithForm where
56 parseJSON = genericParseJSON $ jsonOptions "_wf_"
57 instance ToSchema WithForm where
58 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
60 ------------------------------------------------------------------------
61 type AsyncJobs event ctI input output =
62 AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output
63 ------------------------------------------------------------------------
65 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
67 :> Capture "annuaire_id" AnnuaireId
71 :> AsyncJobs ScraperStatus '[FormUrlEncoded] WithForm ScraperStatus
73 ------------------------------------------------------------------------
74 addToAnnuaireWithForm :: FlowCmdM env err m
77 -> (ScraperStatus -> m ())
79 addToAnnuaireWithForm _cid (WithForm ft _d _l) logStatus = do
85 -- CSV_HAL -> Parser.parseFormat Parser.CsvHal
86 -- CSV -> Parser.parseFormat Parser.CsvGargV3
87 -- WOS -> Parser.parseFormat Parser.WOS
88 -- PresseRIS -> Parser.parseFormat Parser.RisPresse
95 logStatus ScraperStatus { _scst_succeeded = Just 1
96 , _scst_failed = Just 0
97 , _scst_remaining = Just 1
98 , _scst_events = Just []
100 -- cid' <- flowCorpus "user1"
102 -- (Multi $ fromMaybe EN l)
103 -- (map (map toHyperdataDocument) docs)
105 -- printDebug "cid'" cid'
107 pure ScraperStatus { _scst_succeeded = Just 2
108 , _scst_failed = Just 0
109 , _scst_remaining = Just 0
110 , _scst_events = Just []