]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[INI] max docs for scrapers config
[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 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
13
14 {-# LANGUAGE ConstraintKinds #-}
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE KindSignatures #-}
18 {-# LANGUAGE ScopedTypeVariables #-}
19 {-# LANGUAGE TypeFamilies #-}
20 {-# LANGUAGE UndecidableInstances #-}
21
22 ---------------------------------------------------------------------
23 module Gargantext.API.Routes
24 where
25 ---------------------------------------------------------------------
26
27 -- import qualified Gargantext.API.Search as Search
28 import Control.Concurrent (threadDelay)
29 import Control.Lens (view)
30 import Data.Text (Text)
31 import Data.Validity
32 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
33 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
34 import Gargantext.API.Count (CountAPI, count, Query)
35 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
36 import Gargantext.API.Node
37 import Gargantext.API.Prelude
38 import Gargantext.Core.Types.Individu (User(..))
39 import Gargantext.Core.Viz.Graph.API
40 import Gargantext.Database.Prelude (HasConfig(..))
41 import Gargantext.Database.Admin.Types.Hyperdata
42 import Gargantext.Database.Admin.Types.Node
43 import Gargantext.Prelude
44 import Gargantext.Prelude.Config (GargConfig(..))
45 import Servant
46 import Servant.Auth as SA
47 import Servant.Auth.Swagger ()
48 import Servant.Job.Async
49 import Servant.Swagger.UI
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 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 :<|> "annuaire" :> Summary "Annuaire endpoint"
114 :> Capture "annuaire_id" AnnuaireId
115 :> NodeAPI HyperdataAnnuaire
116
117 :<|> "annuaire" :> Summary "Contact endpoint"
118 :> Capture "annuaire_id" NodeId
119 :> Contact.API
120
121 -- Document endpoint
122 :<|> "document" :> Summary "Document endpoint"
123 :> Capture "doc_id" DocId
124 :> "ngrams" :> TableNgramsApi
125
126 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
127 -- TODO-SECURITY
128 :<|> "count" :> Summary "Count endpoint"
129 :> ReqBody '[JSON] Query
130 :> CountAPI
131
132 -- Corpus endpoint --> TODO rename s/search/filter/g
133 -- :<|> "search" :> Capture "corpus" NodeId
134 -- :> (Search.API Search.SearchResult)
135
136 -- TODO move to NodeAPI?
137 :<|> "graph" :> Summary "Graph endpoint"
138 :> Capture "graph_id" NodeId
139 :> GraphAPI
140
141 -- TODO move to NodeAPI?
142 -- Tree endpoint
143 :<|> "tree" :> Summary "Tree endpoint"
144 :> Capture "tree_id" NodeId
145 :> TreeAPI
146
147 -- :<|> New.Upload
148 :<|> New.AddWithForm
149 :<|> New.AddWithFile
150 :<|> New.AddWithQuery
151
152 -- :<|> "annuaire" :> Annuaire.AddWithForm
153 -- :<|> New.AddWithFile
154 -- :<|> "scraper" :> WithCallbacks ScraperAPI
155 -- :<|> "new" :> New.Api
156
157 :<|> "lists" :> Summary "List export API"
158 :> Capture "listId" ListId
159 :> List.API
160
161 :<|> "wait" :> Summary "Wait test"
162 :> Capture "x" Int
163 :> WaitAPI -- Get '[JSON] Int
164
165 -- /mv/<id>/<id>
166 -- /merge/<id>/<id>
167 -- /rename/<id>
168 -- :<|> "static"
169 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
170 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
171 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
172 ---------------------------------------------------------------------
173
174 type API = SwaggerAPI
175 :<|> GargAPI
176 :<|> FrontEndAPI
177
178 -- | API for serving @swagger.json@
179 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
180
181 -- | API for serving main operational routes of @gargantext.org@
182 -- TODO
183 -- /mv/<id>/<id>
184 -- /merge/<id>/<id>
185 -- /rename/<id>
186 -- :<|> "static"
187 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
188 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
189 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
190 ---------------------------------------------------------------------
191
192 ---------------------------------------------------------------------
193 -- | Server declarations
194
195 -- TODO-SECURITY admin only: withAdmin
196 -- Question: How do we mark admins?
197 serverGargAdminAPI :: GargServer GargAdminAPI
198 serverGargAdminAPI = roots
199 :<|> nodesAPI
200
201
202 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
203 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
204 = serverGargAdminAPI
205 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
206 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
207 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
208 :<|> Export.getCorpus -- uid
209 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
210 :<|> Contact.api uid
211
212 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
213 <$> PathNode <*> apiNgramsTableDoc
214
215 :<|> count -- TODO: undefined
216
217 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
218 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
219
220 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
221 <$> PathNode <*> graphAPI uid -- TODO: mock
222
223 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
224 <$> PathNode <*> treeAPI
225 -- TODO access
226 :<|> addCorpusWithForm (RootId (NodeId uid))
227 :<|> addCorpusWithFile (RootId (NodeId uid))
228 :<|> addCorpusWithQuery (RootId (NodeId uid))
229
230 -- :<|> addAnnuaireWithForm
231 -- :<|> New.api uid -- TODO-SECURITY
232 -- :<|> New.info uid -- TODO-SECURITY
233 :<|> List.api
234 :<|> waitAPI
235
236
237 ----------------------------------------------------------------------
238 -- For Tests
239 type WaitAPI = Get '[JSON] Text
240
241 waitAPI :: Int -> GargServer WaitAPI
242 waitAPI n = do
243 let
244 m = (10 :: Int) ^ (6 :: Int)
245 _ <- liftBase $ threadDelay ( m * n)
246 pure $ "Waited: " <> (cs $ show n)
247 ----------------------------------------
248
249 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
250 addCorpusWithQuery user cid =
251 serveJobsAPI $
252 JobFunction (\q log -> do
253 conf <- view hasConfig
254 let limit = Just $ _gc_max_docs_scrapers conf
255 New.addToCorpusWithQuery user cid q limit (liftBase . log)
256 {- let log' x = do
257 printDebug "addToCorpusWithQuery" x
258 liftBase $ log x
259 -}
260 )
261
262 {-
263 addWithFile :: GargServer New.AddWithFile
264 addWithFile cid i f =
265 serveJobsAPI $
266 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
267 -}
268
269 addCorpusWithForm :: User -> GargServer New.AddWithForm
270 addCorpusWithForm user cid =
271 serveJobsAPI $
272 JobFunction (\i log ->
273 let
274 log' x = do
275 printDebug "addToCorpusWithForm" x
276 liftBase $ log x
277 in New.addToCorpusWithForm user cid i log')
278
279 addCorpusWithFile :: User -> GargServer New.AddWithFile
280 addCorpusWithFile user cid =
281 serveJobsAPI $
282 JobFunction (\i log ->
283 let
284 log' x = do
285 printDebug "addToCorpusWithFile" x
286 liftBase $ log x
287 in New.addToCorpusWithFile user cid i log')
288
289 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
290 addAnnuaireWithForm cid =
291 serveJobsAPI $
292 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
293