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 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
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
99 :<|> "corpus" :> Summary "Corpus endpoint"
100 :> Capture "corpus_id" CorpusId
101 :> NodeAPI HyperdataCorpus
103 :<|> "corpus" :> Summary "Corpus endpoint"
104 :> Capture "node1_id" NodeId
106 :> Capture "node2_id" NodeId
107 :> NodeNodeAPI HyperdataAny
109 :<|> "corpus" :> Capture "node_id" CorpusId
113 :<|> "annuaire" :> Summary "Annuaire endpoint"
114 :> Capture "annuaire_id" AnnuaireId
115 :> NodeAPI HyperdataAnnuaire
117 :<|> "annuaire" :> Summary "Contact endpoint"
118 :> Capture "annuaire_id" NodeId
122 :<|> "document" :> Summary "Document endpoint"
123 :> Capture "doc_id" DocId
127 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
129 :<|> "count" :> Summary "Count endpoint"
130 :> ReqBody '[JSON] Query
133 -- Corpus endpoint --> TODO rename s/search/filter/g
134 -- :<|> "search" :> Capture "corpus" NodeId
135 -- :> (Search.API Search.SearchResult)
137 -- TODO move to NodeAPI?
138 :<|> "graph" :> Summary "Graph endpoint"
139 :> Capture "graph_id" NodeId
142 -- TODO move to NodeAPI?
144 :<|> "tree" :> Summary "Tree endpoint"
145 :> Capture "tree_id" NodeId
151 :<|> New.AddWithQuery
153 -- :<|> "annuaire" :> Annuaire.AddWithForm
154 -- :<|> New.AddWithFile
155 -- :<|> "scraper" :> WithCallbacks ScraperAPI
156 -- :<|> "new" :> New.Api
158 :<|> "lists" :> Summary "List export API"
159 :> Capture "listId" ListId
162 :<|> "wait" :> Summary "Wait test"
164 :> WaitAPI -- Get '[JSON] Int
170 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
171 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
172 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
173 ---------------------------------------------------------------------
175 type API = SwaggerAPI
179 -- | API for serving @swagger.json@
180 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
182 -- | API for serving main operational routes of @gargantext.org@
188 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
189 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
190 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
191 ---------------------------------------------------------------------
193 ---------------------------------------------------------------------
194 -- | Server declarations
196 -- TODO-SECURITY admin only: withAdmin
197 -- Question: How do we mark admins?
198 serverGargAdminAPI :: GargServer GargAdminAPI
199 serverGargAdminAPI = roots
203 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
204 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
206 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
207 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
208 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
209 :<|> Export.getCorpus -- uid
210 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
213 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
214 <$> PathNode <*> apiNgramsTableDoc
216 :<|> count -- TODO: undefined
218 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
219 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
221 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
222 <$> PathNode <*> graphAPI uid -- TODO: mock
224 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
225 <$> PathNode <*> treeAPI
227 :<|> addCorpusWithForm (RootId (NodeId uid))
228 :<|> addCorpusWithFile (RootId (NodeId uid))
229 :<|> addCorpusWithQuery (RootId (NodeId uid))
231 -- :<|> addAnnuaireWithForm
232 -- :<|> New.api uid -- TODO-SECURITY
233 -- :<|> New.info uid -- TODO-SECURITY
238 ----------------------------------------------------------------------
240 type WaitAPI = Get '[JSON] Text
242 waitAPI :: Int -> GargServer WaitAPI
245 m = (10 :: Int) ^ (6 :: Int)
246 _ <- liftBase $ threadDelay ( m * n)
247 pure $ "Waited: " <> (cs $ show n)
248 ----------------------------------------
250 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
251 addCorpusWithQuery user cid =
253 JobFunction (\q log -> do
254 limit <- view $ config . gc_max_docs_scrapers
255 New.addToCorpusWithQuery user cid q (Just limit) (liftBase . log)
257 printDebug "addToCorpusWithQuery" x
263 addWithFile :: GargServer New.AddWithFile
264 addWithFile cid i f =
266 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
269 addCorpusWithForm :: User -> GargServer New.AddWithForm
270 addCorpusWithForm user cid =
272 JobFunction (\i log ->
275 printDebug "addToCorpusWithForm" x
277 in New.addToCorpusWithForm user cid i log')
279 addCorpusWithFile :: User -> GargServer New.AddWithFile
280 addCorpusWithFile user cid =
282 JobFunction (\i log ->
285 printDebug "addToCorpusWithFile" x
287 in New.addToCorpusWithFile user cid i log')
289 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
290 addAnnuaireWithForm cid =
292 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))