]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[FEAT] Social lists WithParent class and instances
[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"
124 :> TableNgramsApi
125
126 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
127 -- TODO-SECURITY
128 :<|> "count" :> Summary "Count endpoint"
129 :> ReqBody '[JSON] Query
130 :> CountAPI
131
132 -- Corpus endpoint --> TODO rename s/search/filter/g
133 -- :<|> "search" :> Capture "corpus" NodeId
134 -- :> (Search.API Search.SearchResult)
135
136 -- TODO move to NodeAPI?
137 :<|> "graph" :> Summary "Graph endpoint"
138 :> Capture "graph_id" NodeId
139 :> GraphAPI
140
141 -- TODO move to NodeAPI?
142 -- Tree endpoint
143 :<|> "tree" :> Summary "Tree endpoint"
144 :> Capture "tree_id" NodeId
145 :> TreeAPI
146
147 -- :<|> New.Upload
148 :<|> New.AddWithForm
149 :<|> New.AddWithFile
150 :<|> New.AddWithQuery
151
152 -- :<|> "annuaire" :> Annuaire.AddWithForm
153 -- :<|> New.AddWithFile
154 -- :<|> "scraper" :> WithCallbacks ScraperAPI
155 -- :<|> "new" :> New.Api
156
157 :<|> "lists" :> Summary "List export API"
158 :> Capture "listId" ListId
159 :> List.API
160
161 :<|> "wait" :> Summary "Wait test"
162 :> Capture "x" Int
163 :> WaitAPI -- Get '[JSON] Int
164
165 -- /mv/<id>/<id>
166 -- /merge/<id>/<id>
167 -- /rename/<id>
168 -- :<|> "static"
169 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
170 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
171 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
172 ---------------------------------------------------------------------
173
174 type API = SwaggerAPI
175 :<|> GargAPI
176 :<|> FrontEndAPI
177
178 -- | API for serving @swagger.json@
179 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
180
181 -- | API for serving main operational routes of @gargantext.org@
182 -- TODO
183 -- /mv/<id>/<id>
184 -- /merge/<id>/<id>
185 -- /rename/<id>
186 -- :<|> "static"
187 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
188 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
189 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
190 ---------------------------------------------------------------------
191
192 ---------------------------------------------------------------------
193 -- | Server declarations
194
195 -- TODO-SECURITY admin only: withAdmin
196 -- Question: How do we mark admins?
197 serverGargAdminAPI :: GargServer GargAdminAPI
198 serverGargAdminAPI = roots
199 :<|> nodesAPI
200
201
202 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
203 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
204 = serverGargAdminAPI
205 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
206 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
207 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
208 :<|> Export.getCorpus -- uid
209 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
210 :<|> Contact.api uid
211
212 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
213 <$> PathNode <*> apiNgramsTableDoc
214
215 :<|> count -- TODO: undefined
216
217 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
218 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
219
220 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
221 <$> PathNode <*> graphAPI uid -- TODO: mock
222
223 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
224 <$> PathNode <*> treeAPI
225 -- TODO access
226 :<|> addCorpusWithForm (RootId (NodeId uid))
227 :<|> addCorpusWithFile (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 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
250 addCorpusWithQuery user cid =
251 serveJobsAPI $
252 JobFunction (\q log -> do
253 limit <- view $ config . gc_max_docs_scrapers
254 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log)
255 {- let log' x = do
256 printDebug "addToCorpusWithQuery" x
257 liftBase $ log x
258 -}
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 addCorpusWithFile :: User -> GargServer New.AddWithFile
279 addCorpusWithFile user cid =
280 serveJobsAPI $
281 JobFunction (\i log ->
282 let
283 log' x = do
284 printDebug "addToCorpusWithFile" x
285 liftBase $ log x
286 in New.addToCorpusWithFile user cid i log')
287
288 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
289 addAnnuaireWithForm cid =
290 serveJobsAPI $
291 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
292