2 Module : Gargantext.API.Routes
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE ConstraintKinds #-}
13 {-# LANGUAGE TypeOperators #-}
14 {-# LANGUAGE KindSignatures #-}
15 {-# LANGUAGE ScopedTypeVariables #-}
16 {-# LANGUAGE TypeFamilies #-}
18 module Gargantext.API.Routes
21 import Control.Concurrent (threadDelay)
22 import Control.Lens (view)
23 import Data.Text (Text)
26 import Servant.Auth as SA
27 import Servant.Auth.Swagger ()
28 import Servant.Job.Async
29 import Servant.Swagger.UI
31 import Gargantext.API.Admin.Auth (withAccess)
32 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
33 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
34 import Gargantext.API.Context
35 import Gargantext.API.Count (CountAPI, count, Query)
36 import Gargantext.API.Job (jobLogInit)
37 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
38 import Gargantext.API.Node
39 import Gargantext.API.Prelude
40 import Gargantext.Core.Types.Individu (User(..))
41 import Gargantext.Core.Viz.Graph.API
42 import Gargantext.Database.Admin.Types.Hyperdata
43 import Gargantext.Database.Admin.Types.Node
44 import Gargantext.Database.Prelude (HasConfig(..))
45 import Gargantext.Prelude
46 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
47 import qualified Gargantext.API.GraphQL as GraphQL
48 import qualified Gargantext.API.Ngrams.List as List
49 import qualified Gargantext.API.Node.Contact as Contact
50 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
51 import qualified Gargantext.API.Node.Corpus.Export as CorpusExport
52 import qualified Gargantext.API.Node.Corpus.Export.Types as CorpusExport
53 import qualified Gargantext.API.Node.Corpus.New as New
54 import qualified Gargantext.API.Node.Document.Export as DocumentExport
55 import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport
56 import qualified Gargantext.API.Public as Public
59 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
60 --- | TODO :<|> Summary "Latest API" :> GargAPI'
62 type GargAPIVersion = "v1.0"
63 :> Summary "Garg API Version "
66 type GargVersion = "version"
67 :> Summary "Backend version"
72 "auth" :> Summary "AUTH API"
73 :> ReqBody '[JSON] AuthRequest
74 :> Post '[JSON] AuthResponse
76 -- TODO-ACCESS here we want to request a particular header for
77 -- auth and capabilities.
79 :<|> "public" :> Public.API
82 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
87 = "user" :> Summary "First user endpoint"
89 :<|> "nodes" :> Summary "Nodes endpoint"
90 :> ReqBody '[JSON] [NodeId] :> NodesAPI
92 type GargPrivateAPI' =
96 :<|> "node" :> Summary "Node endpoint"
97 :> Capture "node_id" NodeId
98 :> NodeAPI HyperdataAny
101 :<|> "context" :> Summary "Node endpoint"
102 :> Capture "node_id" ContextId
103 :> ContextAPI HyperdataAny
106 :<|> "corpus" :> Summary "Corpus endpoint"
107 :> Capture "corpus_id" CorpusId
108 :> NodeAPI HyperdataCorpus
110 :<|> "corpus" :> Summary "Corpus endpoint"
111 :> Capture "node1_id" NodeId
113 :> Capture "node2_id" NodeId
114 :> NodeNodeAPI HyperdataAny
116 :<|> "corpus" :> Capture "node_id" CorpusId
121 :<|> "contact" :> Summary "Contact endpoint"
122 :> Capture "contact_id" ContactId
123 :> NodeAPI HyperdataContact
126 :<|> "annuaire" :> Summary "Annuaire endpoint"
127 :> Capture "annuaire_id" AnnuaireId
128 :> NodeAPI HyperdataAnnuaire
130 :<|> "annuaire" :> Summary "Contact endpoint"
131 :> Capture "annuaire_id" NodeId
134 :<|> "document" :> Summary "Document endpoint"
135 :> Capture "doc_id" DocId
139 :<|> "texts" :> Capture "node_id" DocId
140 :> DocumentExport.API
142 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
144 :<|> "count" :> Summary "Count endpoint"
145 :> ReqBody '[JSON] Query
148 -- Corpus endpoint --> TODO rename s/search/filter/g
149 -- :<|> "search" :> Capture "corpus" NodeId
150 -- :> (Search.API Search.SearchResult)
152 -- TODO move to NodeAPI?
153 :<|> "graph" :> Summary "Graph endpoint"
154 :> Capture "graph_id" NodeId
157 -- TODO move to NodeAPI?
159 :<|> "tree" :> Summary "Tree endpoint"
160 :> Capture "tree_id" NodeId
165 -- :<|> New.AddWithFile
166 :<|> New.AddWithQuery
168 -- :<|> "annuaire" :> Annuaire.AddWithForm
169 -- :<|> New.AddWithFile
170 -- :<|> "scraper" :> WithCallbacks ScraperAPI
171 -- :<|> "new" :> New.Api
173 -- TODO refactor the 3 routes below
178 :<|> "wait" :> Summary "Wait test"
180 :> WaitAPI -- Get '[JSON] Int
186 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
187 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
188 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
189 ---------------------------------------------------------------------
191 type API = SwaggerAPI
196 -- | API for serving @swagger.json@
197 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
199 -- | API for serving main operational routes of @gargantext.org@
205 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
206 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
207 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
208 ---------------------------------------------------------------------
210 ---------------------------------------------------------------------
211 -- | Server declarations
213 -- TODO-SECURITY admin only: withAdmin
214 -- Question: How do we mark admins?
215 serverGargAdminAPI :: GargServer GargAdminAPI
216 serverGargAdminAPI = roots
220 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
221 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
223 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
224 :<|> contextAPI (Proxy :: Proxy HyperdataAny) uid
225 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
226 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
227 :<|> CorpusExport.getCorpus -- uid
228 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
229 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
232 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
233 <$> PathNode <*> apiNgramsTableDoc
235 :<|> DocumentExport.api uid
237 :<|> count -- TODO: undefined
239 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
240 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
242 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
243 <$> PathNode <*> graphAPI uid -- TODO: mock
245 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
246 <$> PathNode <*> treeAPI
248 :<|> addCorpusWithForm (RootId (NodeId uid))
249 -- :<|> addCorpusWithFile (RootId (NodeId uid))
250 :<|> addCorpusWithQuery (RootId (NodeId uid))
252 -- :<|> addAnnuaireWithForm
253 -- :<|> New.api uid -- TODO-SECURITY
254 -- :<|> New.info uid -- TODO-SECURITY
261 ----------------------------------------------------------------------
263 type WaitAPI = Get '[JSON] Text
265 waitAPI :: Int -> GargServer WaitAPI
268 m = (10 :: Int) ^ (6 :: Int)
269 _ <- liftBase $ threadDelay ( m * n)
270 pure $ "Waited: " <> (cs $ show n)
271 ----------------------------------------
273 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
274 addCorpusWithQuery user cid =
276 JobFunction (\q log' -> do
277 limit <- view $ hasConfig . gc_max_docs_scrapers
278 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
280 printDebug "addToCorpusWithQuery" x
286 addWithFile :: GargServer New.AddWithFile
287 addWithFile cid i f =
289 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
292 addCorpusWithForm :: User -> GargServer New.AddWithForm
293 addCorpusWithForm user cid =
295 JobFunction (\i log' ->
298 printDebug "[addToCorpusWithForm] " x
300 in New.addToCorpusWithForm user cid i log'' (jobLogInit 3))
302 addCorpusWithFile :: User -> GargServer New.AddWithFile
303 addCorpusWithFile user cid =
305 JobFunction (\i log' ->
308 printDebug "[addToCorpusWithFile]" x
310 in New.addToCorpusWithFile user cid i log'')
312 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
313 addAnnuaireWithForm cid =
315 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))