2 Module : Gargantext.API.Routes
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
14 {-# LANGUAGE ConstraintKinds #-}
15 {-# LANGUAGE TypeOperators #-}
16 {-# LANGUAGE KindSignatures #-}
17 {-# LANGUAGE ScopedTypeVariables #-}
18 {-# LANGUAGE TypeFamilies #-}
20 ---------------------------------------------------------------------
21 module Gargantext.API.Routes
23 ---------------------------------------------------------------------
25 -- import qualified Gargantext.API.Search as Search
26 import Control.Concurrent (threadDelay)
27 import Control.Lens (view)
28 import Data.Text (Text)
31 import Servant.Auth as SA
32 import Servant.Auth.Swagger ()
33 import Servant.Job.Async
34 import Servant.Swagger.UI
36 import qualified Gargantext.API.Ngrams.List as List
37 import qualified Gargantext.API.Node.Contact as Contact
38 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
39 import qualified Gargantext.API.Node.Corpus.Export as CorpusExport
40 import qualified Gargantext.API.Node.Corpus.Export.Types as CorpusExport
41 import qualified Gargantext.API.Node.Corpus.New as New
42 import qualified Gargantext.API.Node.Document.Export as DocumentExport
43 import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport
44 import qualified Gargantext.API.Public as Public
45 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
46 import Gargantext.API.Admin.Auth (withAccess)
47 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
48 import Gargantext.API.Count (CountAPI, count, Query)
49 import qualified Gargantext.API.GraphQL as GraphQL
50 import Gargantext.API.Job (jobLogInit)
51 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
52 import Gargantext.API.Node
53 import Gargantext.API.Prelude
54 import Gargantext.Core.Types.Individu (User(..))
55 import Gargantext.Core.Viz.Graph.API
56 import Gargantext.Database.Prelude (HasConfig(..))
57 import Gargantext.Database.Admin.Types.Hyperdata
58 import Gargantext.Database.Admin.Types.Node
59 import Gargantext.Prelude
60 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
63 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
64 --- | TODO :<|> Summary "Latest API" :> GargAPI'
66 type GargAPIVersion = "v1.0"
67 :> Summary "Garg API Version "
70 type GargVersion = "version"
71 :> Summary "Backend version"
76 "auth" :> Summary "AUTH API"
77 :> ReqBody '[JSON] AuthRequest
78 :> Post '[JSON] AuthResponse
80 -- TODO-ACCESS here we want to request a particular header for
81 -- auth and capabilities.
83 :<|> "public" :> Public.API
86 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
91 = "user" :> Summary "First user endpoint"
93 :<|> "nodes" :> Summary "Nodes endpoint"
94 :> ReqBody '[JSON] [NodeId] :> NodesAPI
96 type GargPrivateAPI' =
100 :<|> "node" :> Summary "Node endpoint"
101 :> Capture "node_id" NodeId
102 :> NodeAPI HyperdataAny
105 :<|> "corpus" :> Summary "Corpus endpoint"
106 :> Capture "corpus_id" CorpusId
107 :> NodeAPI HyperdataCorpus
109 :<|> "corpus" :> Summary "Corpus endpoint"
110 :> Capture "node1_id" NodeId
112 :> Capture "node2_id" NodeId
113 :> NodeNodeAPI HyperdataAny
115 :<|> "corpus" :> Capture "node_id" CorpusId
120 :<|> "contact" :> Summary "Contact endpoint"
121 :> Capture "contact_id" ContactId
122 :> NodeAPI HyperdataContact
125 :<|> "annuaire" :> Summary "Annuaire endpoint"
126 :> Capture "annuaire_id" AnnuaireId
127 :> NodeAPI HyperdataAnnuaire
129 :<|> "annuaire" :> Summary "Contact endpoint"
130 :> Capture "annuaire_id" NodeId
133 :<|> "document" :> Summary "Document endpoint"
134 :> Capture "doc_id" DocId
138 :<|> "texts" :> Capture "node_id" DocId
139 :> DocumentExport.API
141 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
143 :<|> "count" :> Summary "Count endpoint"
144 :> ReqBody '[JSON] Query
147 -- Corpus endpoint --> TODO rename s/search/filter/g
148 -- :<|> "search" :> Capture "corpus" NodeId
149 -- :> (Search.API Search.SearchResult)
151 -- TODO move to NodeAPI?
152 :<|> "graph" :> Summary "Graph endpoint"
153 :> Capture "graph_id" NodeId
156 -- TODO move to NodeAPI?
158 :<|> "tree" :> Summary "Tree endpoint"
159 :> Capture "tree_id" NodeId
164 -- :<|> New.AddWithFile
165 :<|> New.AddWithQuery
167 -- :<|> "annuaire" :> Annuaire.AddWithForm
168 -- :<|> New.AddWithFile
169 -- :<|> "scraper" :> WithCallbacks ScraperAPI
170 -- :<|> "new" :> New.Api
172 -- TODO refactor the 3 routes below
177 :<|> "wait" :> Summary "Wait test"
179 :> WaitAPI -- Get '[JSON] Int
185 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
186 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
187 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
188 ---------------------------------------------------------------------
190 type API = SwaggerAPI
195 -- | API for serving @swagger.json@
196 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
198 -- | API for serving main operational routes of @gargantext.org@
204 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
205 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
206 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
207 ---------------------------------------------------------------------
209 ---------------------------------------------------------------------
210 -- | Server declarations
212 -- TODO-SECURITY admin only: withAdmin
213 -- Question: How do we mark admins?
214 serverGargAdminAPI :: GargServer GargAdminAPI
215 serverGargAdminAPI = roots
219 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
220 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
222 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
223 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
224 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
225 :<|> CorpusExport.getCorpus -- uid
226 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
227 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
230 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
231 <$> PathNode <*> apiNgramsTableDoc
233 :<|> DocumentExport.api uid
235 :<|> count -- TODO: undefined
237 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
238 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
240 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
241 <$> PathNode <*> graphAPI uid -- TODO: mock
243 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
244 <$> PathNode <*> treeAPI
246 :<|> addCorpusWithForm (RootId (NodeId uid))
247 -- :<|> addCorpusWithFile (RootId (NodeId uid))
248 :<|> addCorpusWithQuery (RootId (NodeId uid))
250 -- :<|> addAnnuaireWithForm
251 -- :<|> New.api uid -- TODO-SECURITY
252 -- :<|> New.info uid -- TODO-SECURITY
259 ----------------------------------------------------------------------
261 type WaitAPI = Get '[JSON] Text
263 waitAPI :: Int -> GargServer WaitAPI
266 m = (10 :: Int) ^ (6 :: Int)
267 _ <- liftBase $ threadDelay ( m * n)
268 pure $ "Waited: " <> (cs $ show n)
269 ----------------------------------------
271 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
272 addCorpusWithQuery user cid =
274 JobFunction (\q log' -> do
275 limit <- view $ hasConfig . gc_max_docs_scrapers
276 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
278 printDebug "addToCorpusWithQuery" x
284 addWithFile :: GargServer New.AddWithFile
285 addWithFile cid i f =
287 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
290 addCorpusWithForm :: User -> GargServer New.AddWithForm
291 addCorpusWithForm user cid =
293 JobFunction (\i log' ->
296 printDebug "[addToCorpusWithForm] " x
298 in New.addToCorpusWithForm user cid i log'' (jobLogInit 3))
300 addCorpusWithFile :: User -> GargServer New.AddWithFile
301 addCorpusWithFile user cid =
303 JobFunction (\i log' ->
306 printDebug "[addToCorpusWithFile]" x
308 in New.addToCorpusWithFile user cid i log'')
310 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
311 addAnnuaireWithForm cid =
313 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))