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