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