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 Export
40 import qualified Gargantext.API.Node.Corpus.Export.Types as Export
41 import qualified Gargantext.API.Node.Corpus.New as New
42 import qualified Gargantext.API.Public as Public
43 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
44 import Gargantext.API.Admin.Auth (withAccess)
45 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
46 import Gargantext.API.Count (CountAPI, count, Query)
47 import qualified Gargantext.API.GraphQL as GraphQL
48 import Gargantext.API.Job (jobLogInit)
49 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
50 import Gargantext.API.Node
51 import Gargantext.API.Prelude
52 import Gargantext.Core.Types.Individu (User(..))
53 import Gargantext.Core.Viz.Graph.API
54 import Gargantext.Database.Prelude (HasConfig(..))
55 import Gargantext.Database.Admin.Types.Hyperdata
56 import Gargantext.Database.Admin.Types.Node
57 import Gargantext.Prelude
58 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
61 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
62 --- | TODO :<|> Summary "Latest API" :> GargAPI'
64 type GargAPIVersion = "v1.0"
65 :> Summary "Garg API Version "
68 type GargVersion = "version"
69 :> Summary "Backend version"
74 "auth" :> Summary "AUTH API"
75 :> ReqBody '[JSON] AuthRequest
76 :> Post '[JSON] AuthResponse
78 -- TODO-ACCESS here we want to request a particular header for
79 -- auth and capabilities.
81 :<|> "public" :> Public.API
84 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
89 = "user" :> Summary "First user endpoint"
91 :<|> "nodes" :> Summary "Nodes endpoint"
92 :> ReqBody '[JSON] [NodeId] :> NodesAPI
94 type GargPrivateAPI' =
98 :<|> "node" :> Summary "Node endpoint"
99 :> Capture "node_id" NodeId
100 :> NodeAPI HyperdataAny
103 :<|> "corpus" :> Summary "Corpus endpoint"
104 :> Capture "corpus_id" CorpusId
105 :> NodeAPI HyperdataCorpus
107 :<|> "corpus" :> Summary "Corpus endpoint"
108 :> Capture "node1_id" NodeId
110 :> Capture "node2_id" NodeId
111 :> NodeNodeAPI HyperdataAny
113 :<|> "corpus" :> Capture "node_id" CorpusId
118 :<|> "contact" :> Summary "Contact endpoint"
119 :> Capture "contact_id" ContactId
120 :> NodeAPI HyperdataContact
123 :<|> "annuaire" :> Summary "Annuaire endpoint"
124 :> Capture "annuaire_id" AnnuaireId
125 :> NodeAPI HyperdataAnnuaire
127 :<|> "annuaire" :> Summary "Contact endpoint"
128 :> Capture "annuaire_id" NodeId
131 :<|> "document" :> Summary "Document endpoint"
132 :> Capture "doc_id" DocId
136 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
138 :<|> "count" :> Summary "Count endpoint"
139 :> ReqBody '[JSON] Query
142 -- Corpus endpoint --> TODO rename s/search/filter/g
143 -- :<|> "search" :> Capture "corpus" NodeId
144 -- :> (Search.API Search.SearchResult)
146 -- TODO move to NodeAPI?
147 :<|> "graph" :> Summary "Graph endpoint"
148 :> Capture "graph_id" NodeId
151 -- TODO move to NodeAPI?
153 :<|> "tree" :> Summary "Tree endpoint"
154 :> Capture "tree_id" NodeId
159 -- :<|> New.AddWithFile
160 :<|> New.AddWithQuery
162 -- :<|> "annuaire" :> Annuaire.AddWithForm
163 -- :<|> New.AddWithFile
164 -- :<|> "scraper" :> WithCallbacks ScraperAPI
165 -- :<|> "new" :> New.Api
167 -- TODO refactor the 3 routes below
172 :<|> "wait" :> Summary "Wait test"
174 :> WaitAPI -- Get '[JSON] Int
180 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
181 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
182 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
183 ---------------------------------------------------------------------
185 type API = SwaggerAPI
190 -- | API for serving @swagger.json@
191 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
193 -- | API for serving main operational routes of @gargantext.org@
199 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
200 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
201 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
202 ---------------------------------------------------------------------
204 ---------------------------------------------------------------------
205 -- | Server declarations
207 -- TODO-SECURITY admin only: withAdmin
208 -- Question: How do we mark admins?
209 serverGargAdminAPI :: GargServer GargAdminAPI
210 serverGargAdminAPI = roots
214 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
215 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
217 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
218 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
219 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
220 :<|> Export.getCorpus -- uid
221 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
222 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
225 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
226 <$> PathNode <*> apiNgramsTableDoc
228 :<|> count -- TODO: undefined
230 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
231 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
233 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
234 <$> PathNode <*> graphAPI uid -- TODO: mock
236 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
237 <$> PathNode <*> treeAPI
239 :<|> addCorpusWithForm (RootId (NodeId uid))
240 -- :<|> addCorpusWithFile (RootId (NodeId uid))
241 :<|> addCorpusWithQuery (RootId (NodeId uid))
243 -- :<|> addAnnuaireWithForm
244 -- :<|> New.api uid -- TODO-SECURITY
245 -- :<|> New.info uid -- TODO-SECURITY
252 ----------------------------------------------------------------------
254 type WaitAPI = Get '[JSON] Text
256 waitAPI :: Int -> GargServer WaitAPI
259 m = (10 :: Int) ^ (6 :: Int)
260 _ <- liftBase $ threadDelay ( m * n)
261 pure $ "Waited: " <> (cs $ show n)
262 ----------------------------------------
264 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
265 addCorpusWithQuery user cid =
267 JobFunction (\q log' -> do
268 limit <- view $ hasConfig . gc_max_docs_scrapers
269 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
271 printDebug "addToCorpusWithQuery" x
277 addWithFile :: GargServer New.AddWithFile
278 addWithFile cid i f =
280 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
283 addCorpusWithForm :: User -> GargServer New.AddWithForm
284 addCorpusWithForm user cid =
286 JobFunction (\i log' ->
289 printDebug "[addToCorpusWithForm] " x
291 in New.addToCorpusWithForm user cid i log'' (jobLogInit 3))
293 addCorpusWithFile :: User -> GargServer New.AddWithFile
294 addCorpusWithFile user cid =
296 JobFunction (\i log' ->
299 printDebug "[addToCorpusWithFile]" x
301 in New.addToCorpusWithFile user cid i log'')
303 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
304 addAnnuaireWithForm cid =
306 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))