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