]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
change export
[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 TemplateHaskell #-}
17 {-# LANGUAGE TypeOperators #-}
18 {-# LANGUAGE KindSignatures #-}
19 {-# LANGUAGE ScopedTypeVariables #-}
20 {-# LANGUAGE TypeFamilies #-}
21 {-# LANGUAGE UndecidableInstances #-}
22
23 ---------------------------------------------------------------------
24 module Gargantext.API.Routes
25 where
26 ---------------------------------------------------------------------
27 import Control.Concurrent (threadDelay)
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 Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
37 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
38 import Gargantext.API.Prelude
39 import Gargantext.API.Count (CountAPI, count, Query)
40 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
41 import Gargantext.API.Node
42 import Gargantext.API.Search (SearchPairsAPI, searchPairs)
43 import Gargantext.Core.Types.Individu (User(..))
44 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
45 import Gargantext.Database.Admin.Types.Hyperdata
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 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.Ngrams.List as List
54
55
56
57 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
58 -- | TODO :<|> Summary "Latest API" :> GargAPI'
59
60
61 type GargAPIVersion = "v1.0"
62 :> Summary "Garg API Version "
63 :> GargAPI'
64
65 type GargVersion = "version"
66 :> Summary "Backend version"
67 :> Get '[JSON] Text
68
69 type GargAPI' =
70 -- Auth endpoint
71 "auth" :> Summary "AUTH API"
72 :> ReqBody '[JSON] AuthRequest
73 :> Post '[JSON] AuthResponse
74 :<|> GargVersion
75 -- TODO-ACCESS here we want to request a particular header for
76 -- auth and capabilities.
77 :<|> GargPrivateAPI
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"
120 :> Capture "contact_id" NodeId
121 :> NodeNodeAPI HyperdataContact
122
123 -- Document endpoint
124 :<|> "document" :> Summary "Document endpoint"
125 :> Capture "doc_id" DocId
126 :> "ngrams" :> TableNgramsApi
127
128 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
129 -- TODO-SECURITY
130 :<|> "count" :> Summary "Count endpoint"
131 :> ReqBody '[JSON] Query
132 :> CountAPI
133
134 -- Corpus endpoint --> TODO rename s/search/filter/g
135 :<|> "search" :> Capture "corpus" NodeId
136 :> SearchPairsAPI
137
138 -- TODO move to NodeAPI?
139 :<|> "graph" :> Summary "Graph endpoint"
140 :> Capture "graph_id" NodeId
141 :> GraphAPI
142
143 -- TODO move to NodeAPI?
144 -- Tree endpoint
145 :<|> "tree" :> Summary "Tree endpoint"
146 :> Capture "tree_id" NodeId
147 :> TreeAPI
148
149 -- :<|> New.Upload
150 :<|> New.AddWithForm
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 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
212
213 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
214 <$> PathNode <*> apiNgramsTableDoc
215
216 :<|> count -- TODO: undefined
217
218 :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
219 <$> PathNode <*> searchPairs -- 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 :<|> addCorpusWithQuery (RootId (NodeId uid))
229
230 -- :<|> addAnnuaireWithForm
231 -- :<|> New.api uid -- TODO-SECURITY
232 -- :<|> New.info uid -- TODO-SECURITY
233 :<|> List.api
234 :<|> waitAPI
235
236
237 ----------------------------------------------------------------------
238 -- For Tests
239 type WaitAPI = Get '[JSON] Text
240
241 waitAPI :: Int -> GargServer WaitAPI
242 waitAPI n = do
243 let
244 m = (10 :: Int) ^ (6 :: Int)
245 _ <- liftBase $ threadDelay ( m * n)
246 pure $ "Waited: " <> (cs $ show n)
247 ----------------------------------------
248
249
250 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
251 addCorpusWithQuery user cid =
252 serveJobsAPI $
253 JobFunction (\q log ->
254 let
255 log' x = do
256 printDebug "addToCorpusWithQuery" x
257 liftBase $ log x
258 in New.addToCorpusWithQuery user cid q log'
259 )
260
261 {-
262 addWithFile :: GargServer New.AddWithFile
263 addWithFile cid i f =
264 serveJobsAPI $
265 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
266 -}
267
268 addCorpusWithForm :: User -> GargServer New.AddWithForm
269 addCorpusWithForm user cid =
270 serveJobsAPI $
271 JobFunction (\i log ->
272 let
273 log' x = do
274 printDebug "addToCorpusWithForm" x
275 liftBase $ log x
276 in New.addToCorpusWithForm user cid i log')
277
278 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
279 addAnnuaireWithForm cid =
280 serveJobsAPI $
281 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
282