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