]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/Corpus/Annuaire.hs
Merge branch 'dev-doc-table-cache-issue' of ssh://gitlab.iscpif.fr:20022/gargantext...
[gargantext.git] / src / Gargantext / API / Node / Corpus / Annuaire.hs
1 {-|
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
8 Portability : POSIX
9 -}
10
11 {-# LANGUAGE TemplateHaskell #-}
12 {-# LANGUAGE TypeOperators #-}
13
14 module Gargantext.API.Node.Corpus.Annuaire
15 where
16
17 import Control.Lens hiding (elements)
18 import Data.Aeson
19 import Data.Swagger
20 import Data.Text (Text)
21 import GHC.Generics (Generic)
22 import Servant
23 import Servant.Job.Core
24 import Servant.Job.Types
25 import Servant.Job.Utils (jsonOptions)
26 import Web.FormUrlEncoded (FromForm)
27
28 import qualified Gargantext.API.Node.Corpus.New.File as NewFile
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
35
36
37 type Api = Summary "New Annuaire endpoint"
38 :> Post '[JSON] AnnuaireId
39
40 ------------------------------------------------------------------------
41 ------------------------------------------------------------------------
42 data AnnuaireWithForm = AnnuaireWithForm
43 { _wf_filetype :: !NewFile.FileType
44 , _wf_data :: !Text
45 , _wf_lang :: !(Maybe Lang)
46 } deriving (Eq, Show, Generic)
47
48 makeLenses ''AnnuaireWithForm
49 instance FromForm AnnuaireWithForm
50 instance FromJSON AnnuaireWithForm where
51 parseJSON = genericParseJSON $ jsonOptions "_wf_"
52 instance ToSchema AnnuaireWithForm where
53 declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_wf_")
54
55 ------------------------------------------------------------------------
56 type AsyncJobs event ctI input output =
57 AsyncJobsAPI' 'Unsafe 'Safe ctI '[JSON] Maybe event input output
58 ------------------------------------------------------------------------
59
60 type AddWithForm = Summary "Add with FormUrlEncoded to annuaire endpoint"
61 :> "annuaire"
62 :> Capture "annuaire_id" AnnuaireId
63 :> "add"
64 :> "form"
65 :> "async"
66 :> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog
67
68 ------------------------------------------------------------------------
69 addToAnnuaireWithForm :: FlowCmdM env err m
70 => AnnuaireId
71 -> AnnuaireWithForm
72 -> (JobLog -> m ())
73 -> m JobLog
74 addToAnnuaireWithForm _cid (AnnuaireWithForm ft _d _l) logStatus = do
75
76 printDebug "ft" ft
77
78 logStatus JobLog { _scst_succeeded = Just 1
79 , _scst_failed = Just 0
80 , _scst_remaining = Just 1
81 , _scst_events = Just []
82 }
83 pure JobLog { _scst_succeeded = Just 2
84 , _scst_failed = Just 0
85 , _scst_remaining = Just 0
86 , _scst_events = Just []
87 }
88