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