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