]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[FEAT] reindexing enabled in frontend
[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 :<|> "lists" :> Summary "List export API"
164 :> Capture "listId" ListId
165 :> List.API
166 {-
167 :<|> "wait" :> Summary "Wait test"
168 :> Capture "x" Int
169 :> WaitAPI -- Get '[JSON] Int
170 -}
171 -- /mv/<id>/<id>
172 -- /merge/<id>/<id>
173 -- /rename/<id>
174 -- :<|> "static"
175 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
176 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
177 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
178 ---------------------------------------------------------------------
179
180 type API = SwaggerAPI
181 :<|> GargAPI
182 :<|> FrontEndAPI
183
184 -- | API for serving @swagger.json@
185 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
186
187 -- | API for serving main operational routes of @gargantext.org@
188 -- TODO
189 -- /mv/<id>/<id>
190 -- /merge/<id>/<id>
191 -- /rename/<id>
192 -- :<|> "static"
193 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
194 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
195 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
196 ---------------------------------------------------------------------
197
198 ---------------------------------------------------------------------
199 -- | Server declarations
200
201 -- TODO-SECURITY admin only: withAdmin
202 -- Question: How do we mark admins?
203 serverGargAdminAPI :: GargServer GargAdminAPI
204 serverGargAdminAPI = roots
205 :<|> nodesAPI
206
207
208 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
209 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
210 = serverGargAdminAPI
211 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
212 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
213 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
214 :<|> Export.getCorpus -- uid
215 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
216 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
217 :<|> Contact.api uid
218
219 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
220 <$> PathNode <*> apiNgramsTableDoc
221
222 :<|> count -- TODO: undefined
223
224 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
225 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
226
227 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
228 <$> PathNode <*> graphAPI uid -- TODO: mock
229
230 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
231 <$> PathNode <*> treeAPI
232 -- TODO access
233 :<|> addCorpusWithForm (RootId (NodeId uid))
234 -- :<|> addCorpusWithFile (RootId (NodeId uid))
235 :<|> addCorpusWithQuery (RootId (NodeId uid))
236
237 -- :<|> addAnnuaireWithForm
238 -- :<|> New.api uid -- TODO-SECURITY
239 -- :<|> New.info uid -- TODO-SECURITY
240 :<|> List.api
241 -- :<|> waitAPI
242
243
244 ----------------------------------------------------------------------
245 -- For Tests
246 type WaitAPI = Get '[JSON] Text
247
248 waitAPI :: Int -> GargServer WaitAPI
249 waitAPI n = do
250 let
251 m = (10 :: Int) ^ (6 :: Int)
252 _ <- liftBase $ threadDelay ( m * n)
253 pure $ "Waited: " <> (cs $ show n)
254 ----------------------------------------
255
256 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
257 addCorpusWithQuery user cid =
258 serveJobsAPI $
259 JobFunction (\q log' -> do
260 limit <- view $ hasConfig . gc_max_docs_scrapers
261 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
262 {- let log' x = do
263 printDebug "addToCorpusWithQuery" x
264 liftBase $ log x
265 -}
266 )
267
268 {-
269 addWithFile :: GargServer New.AddWithFile
270 addWithFile cid i f =
271 serveJobsAPI $
272 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
273 -}
274
275 addCorpusWithForm :: User -> GargServer New.AddWithForm
276 addCorpusWithForm user cid =
277 serveJobsAPI $
278 JobFunction (\i log' ->
279 let
280 log'' x = do
281 printDebug "addToCorpusWithForm" x
282 liftBase $ log' x
283 in New.addToCorpusWithForm user cid i log'')
284
285 addCorpusWithFile :: User -> GargServer New.AddWithFile
286 addCorpusWithFile user cid =
287 serveJobsAPI $
288 JobFunction (\i log' ->
289 let
290 log'' x = do
291 printDebug "addToCorpusWithFile" x
292 liftBase $ log' x
293 in New.addToCorpusWithFile user cid i log'')
294
295 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
296 addAnnuaireWithForm cid =
297 serveJobsAPI $
298 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))
299