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