]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[Merge]
[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 Data.Text (Text)
30 import Data.Validity
31 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
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.Admin.Types.Hyperdata
40 import Gargantext.Database.Admin.Types.Node
41 import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
42 import Gargantext.Prelude
43 import Servant
44 import Servant.Auth as SA
45 import Servant.Auth.Swagger ()
46 import Servant.Job.Async
47 import Servant.Swagger.UI
48 import qualified Gargantext.API.Ngrams.List as List
49 import qualified Gargantext.API.Node.Contact as Contact
50 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
51 import qualified Gargantext.API.Node.Corpus.Export as Export
52 import qualified Gargantext.API.Node.Corpus.New as New
53 import qualified Gargantext.API.Public as Public
54
55 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
56 -- | TODO :<|> Summary "Latest API" :> GargAPI'
57
58 type GargAPIVersion = "v1.0"
59 :> Summary "Garg API Version "
60 :> GargAPI'
61
62 type GargVersion = "version"
63 :> Summary "Backend version"
64 :> Get '[JSON] Text
65
66 type GargAPI' =
67 -- Auth endpoint
68 "auth" :> Summary "AUTH API"
69 :> ReqBody '[JSON] AuthRequest
70 :> Post '[JSON] AuthResponse
71 :<|> GargVersion
72 -- TODO-ACCESS here we want to request a particular header for
73 -- auth and capabilities.
74 :<|> GargPrivateAPI
75 :<|> "public" :> Public.API
76
77
78 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
79 :> GargPrivateAPI'
80
81 type GargAdminAPI
82 -- Roots endpoint
83 = "user" :> Summary "First user endpoint"
84 :> Roots
85 :<|> "nodes" :> Summary "Nodes endpoint"
86 :> ReqBody '[JSON] [NodeId] :> NodesAPI
87
88 type GargPrivateAPI' =
89 GargAdminAPI
90
91 -- Node endpoint
92 :<|> "node" :> Summary "Node endpoint"
93 :> Capture "node_id" NodeId
94 :> NodeAPI HyperdataAny
95
96 -- Corpus endpoints
97 :<|> "corpus" :> Summary "Corpus endpoint"
98 :> Capture "corpus_id" CorpusId
99 :> NodeAPI HyperdataCorpus
100
101 :<|> "corpus" :> Summary "Corpus endpoint"
102 :> Capture "node1_id" NodeId
103 :> "document"
104 :> Capture "node2_id" NodeId
105 :> NodeNodeAPI HyperdataAny
106
107 :<|> "corpus" :> Capture "node_id" CorpusId
108 :> Export.API
109
110 -- Annuaire endpoint
111 :<|> "annuaire" :> Summary "Annuaire endpoint"
112 :> Capture "annuaire_id" AnnuaireId
113 :> NodeAPI HyperdataAnnuaire
114
115 :<|> "annuaire" :> Summary "Contact endpoint"
116 :> Capture "annuaire_id" NodeId
117 :> Contact.API
118
119 -- Document endpoint
120 :<|> "document" :> Summary "Document endpoint"
121 :> Capture "doc_id" DocId
122 :> "ngrams" :> TableNgramsApi
123
124 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
125 -- TODO-SECURITY
126 :<|> "count" :> Summary "Count endpoint"
127 :> ReqBody '[JSON] Query
128 :> CountAPI
129
130 -- Corpus endpoint --> TODO rename s/search/filter/g
131 -- :<|> "search" :> Capture "corpus" NodeId
132 -- :> (Search.API Search.SearchResult)
133
134 -- TODO move to NodeAPI?
135 :<|> "graph" :> Summary "Graph endpoint"
136 :> Capture "graph_id" NodeId
137 :> GraphAPI
138
139 -- TODO move to NodeAPI?
140 -- Tree endpoint
141 :<|> "tree" :> Summary "Tree endpoint"
142 :> Capture "tree_id" NodeId
143 :> TreeAPI
144
145 -- :<|> New.Upload
146 :<|> New.AddWithForm
147 :<|> New.AddWithFile
148 :<|> New.AddWithQuery
149
150 -- :<|> "annuaire" :> Annuaire.AddWithForm
151 -- :<|> New.AddWithFile
152 -- :<|> "scraper" :> WithCallbacks ScraperAPI
153 -- :<|> "new" :> New.Api
154
155 :<|> "lists" :> Summary "List export API"
156 :> Capture "listId" ListId
157 :> List.API
158
159 :<|> "wait" :> Summary "Wait test"
160 :> Capture "x" Int
161 :> WaitAPI -- Get '[JSON] Int
162
163 -- /mv/<id>/<id>
164 -- /merge/<id>/<id>
165 -- /rename/<id>
166 -- :<|> "static"
167 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
168 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
169 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
170 ---------------------------------------------------------------------
171
172 type API = SwaggerAPI
173 :<|> GargAPI
174 :<|> FrontEndAPI
175
176 -- | API for serving @swagger.json@
177 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
178
179 -- | API for serving main operational routes of @gargantext.org@
180 -- TODO
181 -- /mv/<id>/<id>
182 -- /merge/<id>/<id>
183 -- /rename/<id>
184 -- :<|> "static"
185 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
186 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
187 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
188 ---------------------------------------------------------------------
189
190 ---------------------------------------------------------------------
191 -- | Server declarations
192
193 -- TODO-SECURITY admin only: withAdmin
194 -- Question: How do we mark admins?
195 serverGargAdminAPI :: GargServer GargAdminAPI
196 serverGargAdminAPI = roots
197 :<|> nodesAPI
198
199
200 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
201 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
202 = serverGargAdminAPI
203 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
204 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
205 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
206 :<|> Export.getCorpus -- uid
207 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
208 :<|> Contact.api uid
209
210 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
211 <$> PathNode <*> apiNgramsTableDoc
212
213 :<|> count -- TODO: undefined
214
215 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
216 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
217
218 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
219 <$> PathNode <*> graphAPI uid -- TODO: mock
220
221 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
222 <$> PathNode <*> treeAPI
223 -- TODO access
224 :<|> addCorpusWithForm (RootId (NodeId uid))
225 :<|> addCorpusWithFile (RootId (NodeId uid))
226 :<|> addCorpusWithQuery (RootId (NodeId uid))
227
228 -- :<|> addAnnuaireWithForm
229 -- :<|> New.api uid -- TODO-SECURITY
230 -- :<|> New.info uid -- TODO-SECURITY
231 :<|> List.api
232 :<|> waitAPI
233
234
235 ----------------------------------------------------------------------
236 -- For Tests
237 type WaitAPI = Get '[JSON] Text
238
239 waitAPI :: Int -> GargServer WaitAPI
240 waitAPI n = do
241 let
242 m = (10 :: Int) ^ (6 :: Int)
243 _ <- liftBase $ threadDelay ( m * n)
244 pure $ "Waited: " <> (cs $ show n)
245 ----------------------------------------
246
247 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
248 addCorpusWithQuery user cid =
249 serveJobsAPI $
250 JobFunction (\q log ->
251 let
252 log' x = do
253 printDebug "addToCorpusWithQuery" x
254 liftBase $ log x
255 in New.addToCorpusWithQuery user cid q log'
256 )
257
258 {-
259 addWithFile :: GargServer New.AddWithFile
260 addWithFile cid i f =
261 serveJobsAPI $
262 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
263 -}
264
265 addCorpusWithForm :: User -> GargServer New.AddWithForm
266 addCorpusWithForm user cid =
267 serveJobsAPI $
268 JobFunction (\i log ->
269 let
270 log' x = do
271 printDebug "addToCorpusWithForm" x
272 liftBase $ log x
273 in New.addToCorpusWithForm user cid i log')
274
275 addCorpusWithFile :: User -> GargServer New.AddWithFile
276 addCorpusWithFile user cid =
277 serveJobsAPI $
278 JobFunction (\i log ->
279 let
280 log' x = do
281 printDebug "addToCorpusWithFile" x
282 liftBase $ log x
283 in New.addToCorpusWithFile user cid i log')
284
285 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
286 addAnnuaireWithForm cid =
287 serveJobsAPI $
288 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
289