]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
Cleaner Jobs API
[gargantext.git] / src / Gargantext / API / Routes.hs
1 {-|
2 Module : Gargantext.API.Routes
3 Description :
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
12 {-# LANGUAGE ConstraintKinds #-}
13 {-# LANGUAGE TypeOperators #-}
14 {-# LANGUAGE KindSignatures #-}
15 {-# LANGUAGE ScopedTypeVariables #-}
16 {-# LANGUAGE TypeFamilies #-}
17
18 module Gargantext.API.Routes
19 where
20
21 import Control.Concurrent (threadDelay)
22 import Control.Lens (view)
23 import Data.Text (Text)
24 import Data.Validity
25 import Servant
26 import Servant.Auth as SA
27 import Servant.Auth.Swagger ()
28 import Servant.Swagger.UI
29
30 import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess)
31 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
32 import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
33 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
34 import Gargantext.API.Context
35 import Gargantext.API.Count (CountAPI, count, Query)
36 import Gargantext.API.Members (MembersAPI, members)
37 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
38 import Gargantext.API.Node
39 import Gargantext.API.Prelude
40 import Gargantext.Core.Types.Individu (User(..))
41 import Gargantext.Core.Viz.Graph.API
42 import Gargantext.Database.Admin.Types.Hyperdata
43 import Gargantext.Database.Admin.Types.Node
44 import Gargantext.Database.Prelude (HasConfig(..))
45 import Gargantext.Prelude
46 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
47 import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
48 import qualified Gargantext.API.GraphQL as GraphQL
49 import qualified Gargantext.API.Ngrams.List as List
50 import qualified Gargantext.API.Node.Contact as Contact
51 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
52 import qualified Gargantext.API.Node.Corpus.Export as CorpusExport
53 import qualified Gargantext.API.Node.Corpus.Export.Types as CorpusExport
54 import qualified Gargantext.API.Node.Corpus.New as New
55 import qualified Gargantext.API.Node.Document.Export as DocumentExport
56 import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport
57 import qualified Gargantext.API.Public as Public
58
59
60 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
61 --- | TODO :<|> Summary "Latest API" :> GargAPI'
62
63 type GargAPIVersion = "v1.0"
64 :> Summary "Garg API Version "
65 :> GargAPI'
66
67 type GargVersion = "version"
68 :> Summary "Backend version"
69 :> Get '[JSON] Text
70
71 type GargAPI' =
72 -- Auth endpoint
73 "auth" :> Summary "AUTH API"
74 :> ReqBody '[JSON] AuthRequest
75 :> Post '[JSON] AuthResponse
76 :<|> "forgot-password" :> ForgotPasswordAPI
77 :<|> "async" :> "forgot-password" :> ForgotPasswordAsyncAPI
78 :<|> GargVersion
79 -- TODO-ACCESS here we want to request a particular header for
80 -- auth and capabilities.
81 :<|> GargPrivateAPI
82 :<|> "public" :> Public.API
83
84
85 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
86 :> GargPrivateAPI'
87
88 type GargAdminAPI
89 -- Roots endpoint
90 = "user" :> Summary "First user endpoint"
91 :> Roots
92 :<|> "nodes" :> Summary "Nodes endpoint"
93 :> ReqBody '[JSON] [NodeId] :> NodesAPI
94
95 type GargPrivateAPI' =
96 GargAdminAPI
97
98 -- Node endpoint
99 :<|> "node" :> Summary "Node endpoint"
100 :> Capture "node_id" NodeId
101 :> NodeAPI HyperdataAny
102
103 -- Context endpoint
104 :<|> "context" :> Summary "Node endpoint"
105 :> Capture "node_id" ContextId
106 :> ContextAPI HyperdataAny
107
108 -- Corpus endpoints
109 :<|> "corpus" :> Summary "Corpus endpoint"
110 :> Capture "corpus_id" CorpusId
111 :> NodeAPI HyperdataCorpus
112
113 :<|> "corpus" :> Summary "Corpus endpoint"
114 :> Capture "node1_id" NodeId
115 :> "document"
116 :> Capture "node2_id" NodeId
117 :> NodeNodeAPI HyperdataAny
118
119 :<|> "corpus" :> Capture "node_id" CorpusId
120 :> CorpusExport.API
121
122 -- Annuaire endpoint
123 {-
124 :<|> "contact" :> Summary "Contact endpoint"
125 :> Capture "contact_id" ContactId
126 :> NodeAPI HyperdataContact
127 --}
128
129 :<|> "annuaire" :> Summary "Annuaire endpoint"
130 :> Capture "annuaire_id" AnnuaireId
131 :> NodeAPI HyperdataAnnuaire
132
133 :<|> "annuaire" :> Summary "Contact endpoint"
134 :> Capture "annuaire_id" NodeId
135 :> Contact.API
136 -- Document endpoint
137 :<|> "document" :> Summary "Document endpoint"
138 :> Capture "doc_id" DocId
139 :> "ngrams"
140 :> TableNgramsApi
141
142 :<|> "texts" :> Capture "node_id" DocId
143 :> DocumentExport.API
144
145 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
146 -- TODO-SECURITY
147 :<|> "count" :> Summary "Count endpoint"
148 :> ReqBody '[JSON] Query
149 :> CountAPI
150
151 -- Corpus endpoint --> TODO rename s/search/filter/g
152 -- :<|> "search" :> Capture "corpus" NodeId
153 -- :> (Search.API Search.SearchResult)
154
155 -- TODO move to NodeAPI?
156 :<|> "graph" :> Summary "Graph endpoint"
157 :> Capture "graph_id" NodeId
158 :> GraphAPI
159
160 -- TODO move to NodeAPI?
161 -- Tree endpoint
162 :<|> "tree" :> Summary "Tree endpoint"
163 :> Capture "tree_id" NodeId
164 :> TreeAPI
165
166 :<|> "members" :> Summary "Team node members"
167 :> MembersAPI
168
169 -- :<|> New.Upload
170 :<|> New.AddWithForm
171 -- :<|> New.AddWithFile
172 :<|> New.AddWithQuery
173
174 -- :<|> "annuaire" :> Annuaire.AddWithForm
175 -- :<|> New.AddWithFile
176 -- :<|> "scraper" :> WithCallbacks ScraperAPI
177 -- :<|> "new" :> New.Api
178
179 -- TODO refactor the 3 routes below
180 :<|> List.GETAPI
181 :<|> List.JSONAPI
182 :<|> List.CSVAPI
183 {-
184 :<|> "wait" :> Summary "Wait test"
185 :> Capture "x" Int
186 :> WaitAPI -- Get '[JSON] Int
187 -}
188 -- /mv/<id>/<id>
189 -- /merge/<id>/<id>
190 -- /rename/<id>
191 -- :<|> "static"
192 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
193 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
194 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
195 ---------------------------------------------------------------------
196
197 type API = SwaggerAPI
198 :<|> GargAPI
199 :<|> GraphQL.API
200 :<|> FrontEndAPI
201
202 -- | API for serving @swagger.json@
203 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
204
205 -- | API for serving main operational routes of @gargantext.org@
206 -- TODO
207 -- /mv/<id>/<id>
208 -- /merge/<id>/<id>
209 -- /rename/<id>
210 -- :<|> "static"
211 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
212 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
213 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
214 ---------------------------------------------------------------------
215
216 ---------------------------------------------------------------------
217 -- | Server declarations
218
219 -- TODO-SECURITY admin only: withAdmin
220 -- Question: How do we mark admins?
221 serverGargAdminAPI :: GargServer GargAdminAPI
222 serverGargAdminAPI = roots
223 :<|> nodesAPI
224
225
226 serverPrivateGargAPI'
227 :: AuthenticatedUser -> ServerT GargPrivateAPI' (GargM Env GargError)
228 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
229 = serverGargAdminAPI
230 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
231 :<|> contextAPI (Proxy :: Proxy HyperdataAny) uid
232 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
233 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
234 :<|> CorpusExport.getCorpus -- uid
235 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
236 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
237 :<|> Contact.api uid
238
239 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
240 <$> PathNode <*> apiNgramsTableDoc
241
242 :<|> DocumentExport.api uid
243
244 :<|> count -- TODO: undefined
245
246 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
247 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
248
249 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
250 <$> PathNode <*> graphAPI uid -- TODO: mock
251
252 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
253 <$> PathNode <*> treeAPI
254
255 :<|> members uid
256 -- TODO access
257 :<|> addCorpusWithForm (RootId (NodeId uid))
258 -- :<|> addCorpusWithFile (RootId (NodeId uid))
259 :<|> addCorpusWithQuery (RootId (NodeId uid))
260
261 -- :<|> addAnnuaireWithForm
262 -- :<|> New.api uid -- TODO-SECURITY
263 -- :<|> New.info uid -- TODO-SECURITY
264 :<|> List.getApi
265 :<|> List.jsonApi
266 :<|> List.csvApi
267 -- :<|> waitAPI
268
269
270 ----------------------------------------------------------------------
271 -- For Tests
272 type WaitAPI = Get '[JSON] Text
273
274 waitAPI :: Int -> GargServer WaitAPI
275 waitAPI n = do
276 let
277 m = (10 :: Int) ^ (6 :: Int)
278 _ <- liftBase $ threadDelay ( m * n)
279 pure $ "Waited: " <> (cs $ show n)
280 ----------------------------------------
281
282 addCorpusWithQuery :: User -> ServerT New.AddWithQuery (GargM Env GargError)
283 addCorpusWithQuery user cid =
284 serveJobsAPI AddCorpusQueryJob $ \jHandle q -> do
285 limit <- view $ hasConfig . gc_max_docs_scrapers
286 New.addToCorpusWithQuery user cid q (Just limit) jHandle
287 {- let log' x = do
288 printDebug "addToCorpusWithQuery" x
289 liftBase $ log x
290 -}
291
292 addCorpusWithForm :: User -> ServerT New.AddWithForm (GargM Env GargError)
293 addCorpusWithForm user cid =
294 serveJobsAPI AddCorpusFormJob $ \jHandle i -> do
295 -- /NOTE(adinapoli)/ Track the initial steps outside 'addToCorpusWithForm', because it's
296 -- called in a few places, and the job status might be different between invocations.
297 markStarted 3 jHandle
298 New.addToCorpusWithForm user cid i jHandle
299
300 addCorpusWithFile :: User -> ServerT New.AddWithFile (GargM Env GargError)
301 addCorpusWithFile user cid =
302 serveJobsAPI AddCorpusFileJob $ \jHandle i ->
303 New.addToCorpusWithFile user cid i jHandle
304
305 addAnnuaireWithForm :: ServerT Annuaire.AddWithForm (GargM Env GargError)
306 addAnnuaireWithForm cid =
307 serveJobsAPI AddAnnuaireFormJob $ \jHandle i ->
308 Annuaire.addToAnnuaireWithForm cid i jHandle