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)
30 import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..))
31 import Gargantext.API.Admin.Auth (withAccess)
32 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
33 import Gargantext.API.Count (CountAPI, count, Query)
34 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
35 import Gargantext.API.Node
36 import Gargantext.API.Prelude
37 import Gargantext.Core.Types.Individu (User(..))
38 import Gargantext.Core.Viz.Graph.API
39 import Gargantext.Database.Prelude (HasConfig(..))
40 import Gargantext.Database.Admin.Types.Hyperdata
41 import Gargantext.Database.Admin.Types.Node
42 import Gargantext.Prelude
43 import Gargantext.Prelude.Config (gc_max_docs_scrapers)
45 import Servant.Auth as SA
46 import Servant.Auth.Swagger ()
47 import Servant.Job.Async
48 import Servant.Swagger.UI
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 Export
53 import qualified Gargantext.API.Node.Corpus.Export.Types as Export
54 import qualified Gargantext.API.Node.Corpus.New as New
55 import qualified Gargantext.API.Public as Public
57 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
58 -- | TODO :<|> Summary "Latest API" :> GargAPI'
60 type GargAPIVersion = "v1.0"
61 :> Summary "Garg API Version "
64 type GargVersion = "version"
65 :> Summary "Backend version"
70 "auth" :> Summary "AUTH API"
71 :> ReqBody '[JSON] AuthRequest
72 :> Post '[JSON] AuthResponse
74 -- TODO-ACCESS here we want to request a particular header for
75 -- auth and capabilities.
77 :<|> "public" :> Public.API
80 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
85 = "user" :> Summary "First user endpoint"
87 :<|> "nodes" :> Summary "Nodes endpoint"
88 :> ReqBody '[JSON] [NodeId] :> NodesAPI
90 type GargPrivateAPI' =
94 :<|> "node" :> Summary "Node endpoint"
95 :> Capture "node_id" NodeId
96 :> NodeAPI HyperdataAny
100 :<|> "corpus" :> Summary "Corpus endpoint"
101 :> Capture "corpus_id" CorpusId
102 :> NodeAPI HyperdataCorpus
105 :<|> "corpus" :> Summary "Corpus endpoint"
106 :> Capture "node1_id" NodeId
108 :> Capture "node2_id" NodeId
109 :> NodeNodeAPI HyperdataAny
111 :<|> "corpus" :> Capture "node_id" CorpusId
116 :<|> "contact" :> Summary "Contact endpoint"
117 :> Capture "contact_id" ContactId
118 :> NodeAPI HyperdataContact
121 :<|> "annuaire" :> Summary "Annuaire endpoint"
122 :> Capture "annuaire_id" AnnuaireId
123 :> NodeAPI HyperdataAnnuaire
125 :<|> "annuaire" :> Summary "Contact endpoint"
126 :> Capture "annuaire_id" NodeId
129 :<|> "document" :> Summary "Document endpoint"
130 :> Capture "doc_id" DocId
134 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
136 :<|> "count" :> Summary "Count endpoint"
137 :> ReqBody '[JSON] Query
140 -- Corpus endpoint --> TODO rename s/search/filter/g
141 -- :<|> "search" :> Capture "corpus" NodeId
142 -- :> (Search.API Search.SearchResult)
144 -- TODO move to NodeAPI?
145 :<|> "graph" :> Summary "Graph endpoint"
146 :> Capture "graph_id" NodeId
149 -- TODO move to NodeAPI?
151 :<|> "tree" :> Summary "Tree endpoint"
152 :> Capture "tree_id" NodeId
158 :<|> New.AddWithQuery
160 -- :<|> "annuaire" :> Annuaire.AddWithForm
161 -- :<|> New.AddWithFile
162 -- :<|> "scraper" :> WithCallbacks ScraperAPI
163 -- :<|> "new" :> New.Api
165 :<|> "lists" :> Summary "List export API"
166 :> Capture "listId" ListId
169 :<|> "wait" :> Summary "Wait test"
171 :> WaitAPI -- Get '[JSON] Int
177 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
178 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
179 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
180 ---------------------------------------------------------------------
182 type API = SwaggerAPI
186 -- | API for serving @swagger.json@
187 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
189 -- | API for serving main operational routes of @gargantext.org@
195 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
196 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
197 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
198 ---------------------------------------------------------------------
200 ---------------------------------------------------------------------
201 -- | Server declarations
203 -- TODO-SECURITY admin only: withAdmin
204 -- Question: How do we mark admins?
205 serverGargAdminAPI :: GargServer GargAdminAPI
206 serverGargAdminAPI = roots
210 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
211 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
213 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
214 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
215 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
216 :<|> Export.getCorpus -- uid
217 -- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
218 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
221 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
222 <$> PathNode <*> apiNgramsTableDoc
224 :<|> count -- TODO: undefined
226 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
227 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
229 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
230 <$> PathNode <*> graphAPI uid -- TODO: mock
232 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
233 <$> PathNode <*> treeAPI
235 :<|> addCorpusWithForm (RootId (NodeId uid))
236 :<|> addCorpusWithFile (RootId (NodeId uid))
237 :<|> addCorpusWithQuery (RootId (NodeId uid))
239 -- :<|> addAnnuaireWithForm
240 -- :<|> New.api uid -- TODO-SECURITY
241 -- :<|> New.info uid -- TODO-SECURITY
246 ----------------------------------------------------------------------
248 type WaitAPI = Get '[JSON] Text
250 waitAPI :: Int -> GargServer WaitAPI
253 m = (10 :: Int) ^ (6 :: Int)
254 _ <- liftBase $ threadDelay ( m * n)
255 pure $ "Waited: " <> (cs $ show n)
256 ----------------------------------------
258 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
259 addCorpusWithQuery user cid =
261 JobFunction (\q log' -> do
262 limit <- view $ hasConfig . gc_max_docs_scrapers
263 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log')
265 printDebug "addToCorpusWithQuery" x
271 addWithFile :: GargServer New.AddWithFile
272 addWithFile cid i f =
274 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
277 addCorpusWithForm :: User -> GargServer New.AddWithForm
278 addCorpusWithForm user cid =
280 JobFunction (\i log' ->
283 printDebug "addToCorpusWithForm" x
285 in New.addToCorpusWithForm user cid i log'')
287 addCorpusWithFile :: User -> GargServer New.AddWithFile
288 addCorpusWithFile user cid =
290 JobFunction (\i log' ->
293 printDebug "addToCorpusWithFile" x
295 in New.addToCorpusWithFile user cid i log'')
297 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
298 addAnnuaireWithForm cid =
300 JobFunction (\i log' -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log'))