]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
Merge branch 'dev-distributional' of ssh://gitlab.iscpif.fr:20022/gargantext/haskell...
[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 --{-
99 -- Corpus endpoints
100 :<|> "corpus" :> Summary "Corpus endpoint"
101 :> Capture "corpus_id" CorpusId
102 :> NodeAPI HyperdataCorpus
103 --}
104
105 :<|> "corpus" :> Summary "Corpus endpoint"
106 :> Capture "node1_id" NodeId
107 :> "document"
108 :> Capture "node2_id" NodeId
109 :> NodeNodeAPI HyperdataAny
110
111 :<|> "corpus" :> Capture "node_id" CorpusId
112 :> Export.API
113
114 -- Annuaire endpoint
115 {-
116 :<|> "contact" :> Summary "Contact endpoint"
117 :> Capture "contact_id" ContactId
118 :> NodeAPI HyperdataContact
119 --}
120
121 :<|> "annuaire" :> Summary "Annuaire endpoint"
122 :> Capture "annuaire_id" AnnuaireId
123 :> NodeAPI HyperdataAnnuaire
124
125 :<|> "annuaire" :> Summary "Contact endpoint"
126 :> Capture "annuaire_id" NodeId
127 :> Contact.API
128 -- Document endpoint
129 :<|> "document" :> Summary "Document endpoint"
130 :> Capture "doc_id" DocId
131 :> "ngrams"
132 :> TableNgramsApi
133
134 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
135 -- TODO-SECURITY
136 :<|> "count" :> Summary "Count endpoint"
137 :> ReqBody '[JSON] Query
138 :> CountAPI
139
140 -- Corpus endpoint --> TODO rename s/search/filter/g
141 -- :<|> "search" :> Capture "corpus" NodeId
142 -- :> (Search.API Search.SearchResult)
143
144 -- TODO move to NodeAPI?
145 :<|> "graph" :> Summary "Graph endpoint"
146 :> Capture "graph_id" NodeId
147 :> GraphAPI
148
149 -- TODO move to NodeAPI?
150 -- Tree endpoint
151 :<|> "tree" :> Summary "Tree endpoint"
152 :> Capture "tree_id" NodeId
153 :> TreeAPI
154
155 -- :<|> New.Upload
156 :<|> New.AddWithForm
157 :<|> New.AddWithFile
158 :<|> New.AddWithQuery
159
160 -- :<|> "annuaire" :> Annuaire.AddWithForm
161 -- :<|> New.AddWithFile
162 -- :<|> "scraper" :> WithCallbacks ScraperAPI
163 -- :<|> "new" :> New.Api
164
165 :<|> "lists" :> Summary "List export API"
166 :> Capture "listId" ListId
167 :> List.API
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.api
243 -- :<|> waitAPI
244
245
246 ----------------------------------------------------------------------
247 -- For Tests
248 type WaitAPI = Get '[JSON] Text
249
250 waitAPI :: Int -> GargServer WaitAPI
251 waitAPI n = do
252 let
253 m = (10 :: Int) ^ (6 :: Int)
254 _ <- liftBase $ threadDelay ( m * n)
255 pure $ "Waited: " <> (cs $ show n)
256 ----------------------------------------
257
258 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
259 addCorpusWithQuery user cid =
260 serveJobsAPI $
261 JobFunction (\q log' -> do
262 limit <- view $ hasConfig . gc_max_docs_scrapers
263 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
264 {- let log' x = do
265 printDebug "addToCorpusWithQuery" x
266 liftBase $ log x
267 -}
268 )
269
270 {-
271 addWithFile :: GargServer New.AddWithFile
272 addWithFile cid i f =
273 serveJobsAPI $
274 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
275 -}
276
277 addCorpusWithForm :: User -> GargServer New.AddWithForm
278 addCorpusWithForm user cid =
279 serveJobsAPI $
280 JobFunction (\i log' ->
281 let
282 log'' x = do
283 printDebug "addToCorpusWithForm" x
284 liftBase $ log' x
285 in New.addToCorpusWithForm user cid i log'')
286
287 addCorpusWithFile :: User -> GargServer New.AddWithFile
288 addCorpusWithFile user cid =
289 serveJobsAPI $
290 JobFunction (\i log' ->
291 let
292 log'' x = do
293 printDebug "addToCorpusWithFile" x
294 liftBase $ log' x
295 in New.addToCorpusWithFile user cid i log'')
296
297 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
298 addAnnuaireWithForm cid =
299 serveJobsAPI $
300 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))
301