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