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