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.Swagger.UI
30 import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess)
31 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
32 import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
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 Gargantext.Utils.Jobs (serveJobsAPI)
48 import qualified Gargantext.API.GraphQL as GraphQL
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 CorpusExport
53 import qualified Gargantext.API.Node.Corpus.Export.Types as CorpusExport
54 import qualified Gargantext.API.Node.Corpus.New as New
55 import qualified Gargantext.API.Node.Document.Export as DocumentExport
56 import qualified Gargantext.API.Node.Document.Export.Types as DocumentExport
57 import qualified Gargantext.API.Public as Public
60 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
61 --- | TODO :<|> Summary "Latest API" :> GargAPI'
63 type GargAPIVersion = "v1.0"
64 :> Summary "Garg API Version "
67 type GargVersion = "version"
68 :> Summary "Backend version"
73 "auth" :> Summary "AUTH API"
74 :> ReqBody '[JSON] AuthRequest
75 :> Post '[JSON] AuthResponse
76 :<|> "forgot-password" :> ForgotPasswordAPI
77 :<|> "async" :> "forgot-password" :> ForgotPasswordAsyncAPI
79 -- TODO-ACCESS here we want to request a particular header for
80 -- auth and capabilities.
82 :<|> "public" :> Public.API
85 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
90 = "user" :> Summary "First user endpoint"
92 :<|> "nodes" :> Summary "Nodes endpoint"
93 :> ReqBody '[JSON] [NodeId] :> NodesAPI
95 type GargPrivateAPI' =
99 :<|> "node" :> Summary "Node endpoint"
100 :> Capture "node_id" NodeId
101 :> NodeAPI HyperdataAny
104 :<|> "context" :> Summary "Node endpoint"
105 :> Capture "node_id" ContextId
106 :> ContextAPI HyperdataAny
109 :<|> "corpus" :> Summary "Corpus endpoint"
110 :> Capture "corpus_id" CorpusId
111 :> NodeAPI HyperdataCorpus
113 :<|> "corpus" :> Summary "Corpus endpoint"
114 :> Capture "node1_id" NodeId
116 :> Capture "node2_id" NodeId
117 :> NodeNodeAPI HyperdataAny
119 :<|> "corpus" :> Capture "node_id" CorpusId
124 :<|> "contact" :> Summary "Contact endpoint"
125 :> Capture "contact_id" ContactId
126 :> NodeAPI HyperdataContact
129 :<|> "annuaire" :> Summary "Annuaire endpoint"
130 :> Capture "annuaire_id" AnnuaireId
131 :> NodeAPI HyperdataAnnuaire
133 :<|> "annuaire" :> Summary "Contact endpoint"
134 :> Capture "annuaire_id" NodeId
137 :<|> "document" :> Summary "Document endpoint"
138 :> Capture "doc_id" DocId
142 :<|> "texts" :> Capture "node_id" DocId
143 :> DocumentExport.API
145 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
147 :<|> "count" :> Summary "Count endpoint"
148 :> ReqBody '[JSON] Query
151 -- Corpus endpoint --> TODO rename s/search/filter/g
152 -- :<|> "search" :> Capture "corpus" NodeId
153 -- :> (Search.API Search.SearchResult)
155 -- TODO move to NodeAPI?
156 :<|> "graph" :> Summary "Graph endpoint"
157 :> Capture "graph_id" NodeId
160 -- TODO move to NodeAPI?
162 :<|> "tree" :> Summary "Tree endpoint"
163 :> Capture "tree_id" NodeId
168 -- :<|> New.AddWithFile
169 :<|> New.AddWithQuery
171 -- :<|> "annuaire" :> Annuaire.AddWithForm
172 -- :<|> New.AddWithFile
173 -- :<|> "scraper" :> WithCallbacks ScraperAPI
174 -- :<|> "new" :> New.Api
176 -- TODO refactor the 3 routes below
181 :<|> "wait" :> Summary "Wait test"
183 :> WaitAPI -- Get '[JSON] Int
189 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
190 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
191 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
192 ---------------------------------------------------------------------
194 type API = SwaggerAPI
199 -- | API for serving @swagger.json@
200 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
202 -- | API for serving main operational routes of @gargantext.org@
208 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
209 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
210 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
211 ---------------------------------------------------------------------
213 ---------------------------------------------------------------------
214 -- | Server declarations
216 -- TODO-SECURITY admin only: withAdmin
217 -- Question: How do we mark admins?
218 serverGargAdminAPI :: GargServer GargAdminAPI
219 serverGargAdminAPI = roots
223 serverPrivateGargAPI'
224 :: AuthenticatedUser -> ServerT GargPrivateAPI' (GargM Env GargError)
225 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
227 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
228 :<|> contextAPI (Proxy :: Proxy HyperdataAny) uid
229 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
230 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
231 :<|> CorpusExport.getCorpus -- uid
232 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
233 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
236 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
237 <$> PathNode <*> apiNgramsTableDoc
239 :<|> DocumentExport.api uid
241 :<|> count -- TODO: undefined
243 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
244 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
246 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
247 <$> PathNode <*> graphAPI uid -- TODO: mock
249 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
250 <$> PathNode <*> treeAPI
252 :<|> addCorpusWithForm (RootId (NodeId uid))
253 -- :<|> addCorpusWithFile (RootId (NodeId uid))
254 :<|> addCorpusWithQuery (RootId (NodeId uid))
256 -- :<|> addAnnuaireWithForm
257 -- :<|> New.api uid -- TODO-SECURITY
258 -- :<|> New.info uid -- TODO-SECURITY
265 ----------------------------------------------------------------------
267 type WaitAPI = Get '[JSON] Text
269 waitAPI :: Int -> GargServer WaitAPI
272 m = (10 :: Int) ^ (6 :: Int)
273 _ <- liftBase $ threadDelay ( m * n)
274 pure $ "Waited: " <> (cs $ show n)
275 ----------------------------------------
277 addCorpusWithQuery :: User -> ServerT New.AddWithQuery (GargM Env GargError)
278 addCorpusWithQuery user cid =
279 serveJobsAPI AddCorpusQueryJob $ \q log' -> do
280 limit <- view $ hasConfig . gc_max_docs_scrapers
281 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
283 printDebug "addToCorpusWithQuery" x
287 addCorpusWithForm :: User -> ServerT New.AddWithForm (GargM Env GargError)
288 addCorpusWithForm user cid =
289 serveJobsAPI AddCorpusFormJob $ \i log' ->
292 printDebug "[addToCorpusWithForm] " x
294 in New.addToCorpusWithForm user cid i log'' (jobLogInit 3)
296 addCorpusWithFile :: User -> ServerT New.AddWithFile (GargM Env GargError)
297 addCorpusWithFile user cid =
298 serveJobsAPI AddCorpusFileJob $ \i log' ->
301 printDebug "[addToCorpusWithFile]" x
303 in New.addToCorpusWithFile user cid i log''
305 addAnnuaireWithForm :: ServerT Annuaire.AddWithForm (GargM Env GargError)
306 addAnnuaireWithForm cid =
307 serveJobsAPI AddAnnuaireFormJob $ \i log' ->
308 Annuaire.addToAnnuaireWithForm cid i (liftBase . log')