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