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