]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[FIX] Shared lists is taken into account now
[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 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 :<|> "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"
125 :> TableNgramsApi
126
127 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
128 -- TODO-SECURITY
129 :<|> "count" :> Summary "Count endpoint"
130 :> ReqBody '[JSON] Query
131 :> CountAPI
132
133 -- Corpus endpoint --> TODO rename s/search/filter/g
134 -- :<|> "search" :> Capture "corpus" NodeId
135 -- :> (Search.API Search.SearchResult)
136
137 -- TODO move to NodeAPI?
138 :<|> "graph" :> Summary "Graph endpoint"
139 :> Capture "graph_id" NodeId
140 :> GraphAPI
141
142 -- TODO move to NodeAPI?
143 -- Tree endpoint
144 :<|> "tree" :> Summary "Tree endpoint"
145 :> Capture "tree_id" NodeId
146 :> TreeAPI
147
148 -- :<|> New.Upload
149 :<|> New.AddWithForm
150 :<|> New.AddWithFile
151 :<|> New.AddWithQuery
152
153 -- :<|> "annuaire" :> Annuaire.AddWithForm
154 -- :<|> New.AddWithFile
155 -- :<|> "scraper" :> WithCallbacks ScraperAPI
156 -- :<|> "new" :> New.Api
157
158 :<|> "lists" :> Summary "List export API"
159 :> Capture "listId" ListId
160 :> List.API
161
162 :<|> "wait" :> Summary "Wait test"
163 :> Capture "x" Int
164 :> WaitAPI -- Get '[JSON] Int
165
166 -- /mv/<id>/<id>
167 -- /merge/<id>/<id>
168 -- /rename/<id>
169 -- :<|> "static"
170 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
171 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
172 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
173 ---------------------------------------------------------------------
174
175 type API = SwaggerAPI
176 :<|> GargAPI
177 :<|> FrontEndAPI
178
179 -- | API for serving @swagger.json@
180 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
181
182 -- | API for serving main operational routes of @gargantext.org@
183 -- TODO
184 -- /mv/<id>/<id>
185 -- /merge/<id>/<id>
186 -- /rename/<id>
187 -- :<|> "static"
188 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
189 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
190 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
191 ---------------------------------------------------------------------
192
193 ---------------------------------------------------------------------
194 -- | Server declarations
195
196 -- TODO-SECURITY admin only: withAdmin
197 -- Question: How do we mark admins?
198 serverGargAdminAPI :: GargServer GargAdminAPI
199 serverGargAdminAPI = roots
200 :<|> nodesAPI
201
202
203 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
204 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
205 = serverGargAdminAPI
206 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
207 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
208 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
209 :<|> Export.getCorpus -- uid
210 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
211 :<|> Contact.api uid
212
213 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
214 <$> PathNode <*> apiNgramsTableDoc
215
216 :<|> count -- TODO: undefined
217
218 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
219 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
220
221 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
222 <$> PathNode <*> graphAPI uid -- TODO: mock
223
224 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
225 <$> PathNode <*> treeAPI
226 -- TODO access
227 :<|> addCorpusWithForm (RootId (NodeId uid))
228 :<|> addCorpusWithFile (RootId (NodeId uid))
229 :<|> addCorpusWithQuery (RootId (NodeId uid))
230
231 -- :<|> addAnnuaireWithForm
232 -- :<|> New.api uid -- TODO-SECURITY
233 -- :<|> New.info uid -- TODO-SECURITY
234 :<|> List.api
235 :<|> waitAPI
236
237
238 ----------------------------------------------------------------------
239 -- For Tests
240 type WaitAPI = Get '[JSON] Text
241
242 waitAPI :: Int -> GargServer WaitAPI
243 waitAPI n = do
244 let
245 m = (10 :: Int) ^ (6 :: Int)
246 _ <- liftBase $ threadDelay ( m * n)
247 pure $ "Waited: " <> (cs $ show n)
248 ----------------------------------------
249
250 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
251 addCorpusWithQuery user cid =
252 serveJobsAPI $
253 JobFunction (\q log -> do
254 limit <- view $ config . gc_max_docs_scrapers
255 New.addToCorpusWithQuery user cid q (Just 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