]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Routes.hs
[API FIX] search docs ok
[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 {-# LANGUAGE UndecidableInstances #-}
21
22 ---------------------------------------------------------------------
23 module Gargantext.API.Routes
24 where
25 ---------------------------------------------------------------------
26
27 import Control.Concurrent (threadDelay)
28 import Data.Text (Text)
29 import Data.Validity
30 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
31 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
32 import Gargantext.API.Count (CountAPI, count, Query)
33 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
34 import Gargantext.API.Node
35 import Gargantext.API.Prelude
36 -- import qualified Gargantext.API.Search as Search
37 import Gargantext.Core.Types.Individu (User(..))
38 import Gargantext.Database.Admin.Types.Hyperdata
39 import Gargantext.Database.Admin.Types.Node
40 import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
41 import Gargantext.Prelude
42 import Gargantext.Viz.Graph.API
43 import Servant
44 import Servant.Auth as SA
45 import Servant.Auth.Swagger ()
46 import Servant.Job.Async
47 import Servant.Swagger.UI
48 import qualified Gargantext.API.Ngrams.List as List
49 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
50 import qualified Gargantext.API.Node.Corpus.Export as Export
51 import qualified Gargantext.API.Node.Corpus.New as New
52 import qualified Gargantext.API.Public as Public
53 import qualified Gargantext.API.Node.Contact as Contact
54
55 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
56 -- | TODO :<|> Summary "Latest API" :> GargAPI'
57
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.AddWithQuery
149
150 -- :<|> "annuaire" :> Annuaire.AddWithForm
151 -- :<|> New.AddWithFile
152 -- :<|> "scraper" :> WithCallbacks ScraperAPI
153 -- :<|> "new" :> New.Api
154
155 :<|> "lists" :> Summary "List export API"
156 :> Capture "listId" ListId
157 :> List.API
158
159 :<|> "wait" :> Summary "Wait test"
160 :> Capture "x" Int
161 :> WaitAPI -- Get '[JSON] Int
162
163 -- /mv/<id>/<id>
164 -- /merge/<id>/<id>
165 -- /rename/<id>
166 -- :<|> "static"
167 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
168 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
169 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
170 ---------------------------------------------------------------------
171
172 type API = SwaggerAPI
173 :<|> GargAPI
174 :<|> FrontEndAPI
175
176 -- | API for serving @swagger.json@
177 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
178
179 -- | API for serving main operational routes of @gargantext.org@
180 -- TODO
181 -- /mv/<id>/<id>
182 -- /merge/<id>/<id>
183 -- /rename/<id>
184 -- :<|> "static"
185 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
186 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
187 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
188 ---------------------------------------------------------------------
189
190 ---------------------------------------------------------------------
191 -- | Server declarations
192
193 -- TODO-SECURITY admin only: withAdmin
194 -- Question: How do we mark admins?
195 serverGargAdminAPI :: GargServer GargAdminAPI
196 serverGargAdminAPI = roots
197 :<|> nodesAPI
198
199
200 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
201 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
202 = serverGargAdminAPI
203 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
204 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
205 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
206 :<|> Export.getCorpus -- uid
207 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
208 :<|> Contact.api uid
209
210 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
211 <$> PathNode <*> apiNgramsTableDoc
212
213 :<|> count -- TODO: undefined
214
215 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
216 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
217
218 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
219 <$> PathNode <*> graphAPI uid -- TODO: mock
220
221 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
222 <$> PathNode <*> treeAPI
223 -- TODO access
224 :<|> addCorpusWithForm (RootId (NodeId uid))
225 :<|> addCorpusWithQuery (RootId (NodeId uid))
226
227 -- :<|> addAnnuaireWithForm
228 -- :<|> New.api uid -- TODO-SECURITY
229 -- :<|> New.info uid -- TODO-SECURITY
230 :<|> List.api
231 :<|> waitAPI
232
233
234 ----------------------------------------------------------------------
235 -- For Tests
236 type WaitAPI = Get '[JSON] Text
237
238 waitAPI :: Int -> GargServer WaitAPI
239 waitAPI n = do
240 let
241 m = (10 :: Int) ^ (6 :: Int)
242 _ <- liftBase $ threadDelay ( m * n)
243 pure $ "Waited: " <> (cs $ show n)
244 ----------------------------------------
245
246 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
247 addCorpusWithQuery user cid =
248 serveJobsAPI $
249 JobFunction (\q log ->
250 let
251 log' x = do
252 printDebug "addToCorpusWithQuery" x
253 liftBase $ log x
254 in New.addToCorpusWithQuery user cid q log'
255 )
256
257 {-
258 addWithFile :: GargServer New.AddWithFile
259 addWithFile cid i f =
260 serveJobsAPI $
261 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
262 -}
263
264 addCorpusWithForm :: User -> GargServer New.AddWithForm
265 addCorpusWithForm user cid =
266 serveJobsAPI $
267 JobFunction (\i log ->
268 let
269 log' x = do
270 printDebug "addToCorpusWithForm" x
271 liftBase $ log x
272 in New.addToCorpusWithForm user cid i log')
273
274 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
275 addAnnuaireWithForm cid =
276 serveJobsAPI $
277 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
278