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
33 import Gargantext.Utils.Jobs (MonadJobStatus(..))
36 type Api = Summary "New Annuaire endpoint"
37 :> Post '[JSON] AnnuaireId
39 ------------------------------------------------------------------------
40 ------------------------------------------------------------------------
41 data AnnuaireWithForm = AnnuaireWithForm
42 { _wf_filetype :: !NewTypes.FileType
44 , _wf_lang :: !(Maybe Lang)
45 } deriving (Eq, Show, Generic)
47 makeLenses ''AnnuaireWithForm
48 instance FromForm AnnuaireWithForm
49 instance FromJSON AnnuaireWithForm where
50 parseJSON = genericParseJSON $ jsonOptions "_wf_"
51 instance ToJSON AnnuaireWithForm where
52 toJSON = genericToJSON $ jsonOptions "_wf_"
54 instance ToSchema AnnuaireWithForm where
55 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
57 ------------------------------------------------------------------------
59 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
61 :> Capture "annuaire_id" AnnuaireId
65 :> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog
67 ------------------------------------------------------------------------
68 addToAnnuaireWithForm :: (FlowCmdM env err m, MonadJobStatus m)
73 addToAnnuaireWithForm _cid (AnnuaireWithForm { _wf_filetype }) jobHandle = do
75 -- printDebug "ft" _wf_filetype
77 markStarted 3 jobHandle
78 markProgress 1 jobHandle
79 markComplete jobHandle