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 TemplateHaskell #-}
12 {-# LANGUAGE TypeOperators #-}
14 module Gargantext.API.Node.Corpus.Annuaire
17 import Control.Lens hiding (elements)
20 import Data.Text (Text)
21 import GHC.Generics (Generic)
23 import Servant.Job.Core
24 import Servant.Job.Types
25 import Servant.Job.Utils (jsonOptions)
26 import Web.FormUrlEncoded (FromForm)
28 import qualified Gargantext.API.Node.Corpus.New.Types as NewTypes
29 import Gargantext.API.Admin.Orchestrator.Types hiding (AsyncJobs)
30 import Gargantext.Core (Lang(..))
31 import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
32 import Gargantext.Database.Action.Flow.Types (FlowCmdM) -- flowAnnuaire
33 import Gargantext.Database.Admin.Types.Node (AnnuaireId)
34 import Gargantext.Prelude
37 type Api = Summary "New Annuaire endpoint"
38 :> Post '[JSON] AnnuaireId
40 ------------------------------------------------------------------------
41 ------------------------------------------------------------------------
42 data AnnuaireWithForm = AnnuaireWithForm
43 { _wf_filetype :: !NewTypes.FileType
45 , _wf_lang :: !(Maybe Lang)
46 } deriving (Eq, Show, Generic)
48 makeLenses ''AnnuaireWithForm
49 instance FromForm AnnuaireWithForm
50 instance FromJSON AnnuaireWithForm where
51 parseJSON = genericParseJSON $ jsonOptions "_wf_"
52 instance ToJSON AnnuaireWithForm where
53 toJSON = genericToJSON $ jsonOptions "_wf_"
55 instance ToSchema AnnuaireWithForm where
56 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
58 ------------------------------------------------------------------------
59 type AsyncJobs event ctI input output =
60 AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output
61 ------------------------------------------------------------------------
63 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
65 :> Capture "annuaire_id" AnnuaireId
69 :> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog
71 ------------------------------------------------------------------------
72 addToAnnuaireWithForm :: FlowCmdM env err m
77 addToAnnuaireWithForm _cid (AnnuaireWithForm { _wf_filetype }) logStatus = do
79 -- printDebug "ft" _wf_filetype
81 logStatus JobLog { _scst_succeeded = Just 1
82 , _scst_failed = Just 0
83 , _scst_remaining = Just 1
84 , _scst_events = Just []
86 pure JobLog { _scst_succeeded = Just 2
87 , _scst_failed = Just 0
88 , _scst_remaining = Just 0
89 , _scst_events = Just []