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.Utils (jsonOptions)
24 import Web.FormUrlEncoded (FromForm)
26 import qualified Gargantext.API.Node.Corpus.New.Types as NewTypes
27 import Gargantext.API.Admin.Orchestrator.Types
28 import Gargantext.Core (Lang(..))
29 import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
30 import Gargantext.Database.Action.Flow.Types (FlowCmdM) -- flowAnnuaire
31 import Gargantext.Database.Admin.Types.Node (AnnuaireId)
32 import Gargantext.Prelude
35 type Api = Summary "New Annuaire endpoint"
36 :> Post '[JSON] AnnuaireId
38 ------------------------------------------------------------------------
39 ------------------------------------------------------------------------
40 data AnnuaireWithForm = AnnuaireWithForm
41 { _wf_filetype :: !NewTypes.FileType
43 , _wf_lang :: !(Maybe Lang)
44 } deriving (Eq, Show, Generic)
46 makeLenses ''AnnuaireWithForm
47 instance FromForm AnnuaireWithForm
48 instance FromJSON AnnuaireWithForm where
49 parseJSON = genericParseJSON $ jsonOptions "_wf_"
50 instance ToJSON AnnuaireWithForm where
51 toJSON = genericToJSON $ jsonOptions "_wf_"
53 instance ToSchema AnnuaireWithForm where
54 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
56 ------------------------------------------------------------------------
58 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
60 :> Capture "annuaire_id" AnnuaireId
64 :> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog
66 ------------------------------------------------------------------------
67 addToAnnuaireWithForm :: FlowCmdM env err m
72 addToAnnuaireWithForm _cid (AnnuaireWithForm { _wf_filetype }) logStatus = do
74 -- printDebug "ft" _wf_filetype
76 logStatus JobLog { _scst_succeeded = Just 1
77 , _scst_failed = Just 0
78 , _scst_remaining = Just 1
79 , _scst_events = Just []
81 pure JobLog { _scst_succeeded = Just 2
82 , _scst_failed = Just 0
83 , _scst_remaining = Just 0
84 , _scst_events = Just []