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 TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# LANGUAGE KindSignatures #-}
18 {-# LANGUAGE ScopedTypeVariables #-}
19 {-# LANGUAGE TypeFamilies #-}
20 {-# LANGUAGE UndecidableInstances #-}
22 ---------------------------------------------------------------------
23 module Gargantext.API.Routes
25 ---------------------------------------------------------------------
27 -- import qualified Gargantext.API.Search as Search
28 import Control.Concurrent (threadDelay)
29 -- import Control.Lens (view)
30 import Data.Text (Text)
32 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
33 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
34 import Gargantext.API.Count (CountAPI, count, Query)
35 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
36 import Gargantext.API.Node
37 import Gargantext.API.Prelude
38 import Gargantext.Core.Types.Individu (User(..))
39 import Gargantext.Core.Viz.Graph.API
40 -- import Gargantext.Database.Prelude (HasConfig(..))
41 import Gargantext.Database.Admin.Types.Hyperdata
42 import Gargantext.Database.Admin.Types.Node
43 import Gargantext.Prelude
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.New as New
54 import qualified Gargantext.API.Public as Public
56 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
57 -- | TODO :<|> Summary "Latest API" :> GargAPI'
59 type GargAPIVersion = "v1.0"
60 :> Summary "Garg API Version "
63 type GargVersion = "version"
64 :> Summary "Backend version"
69 "auth" :> Summary "AUTH API"
70 :> ReqBody '[JSON] AuthRequest
71 :> Post '[JSON] AuthResponse
73 -- TODO-ACCESS here we want to request a particular header for
74 -- auth and capabilities.
76 :<|> "public" :> Public.API
79 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
84 = "user" :> Summary "First user endpoint"
86 :<|> "nodes" :> Summary "Nodes endpoint"
87 :> ReqBody '[JSON] [NodeId] :> NodesAPI
89 type GargPrivateAPI' =
93 :<|> "node" :> Summary "Node endpoint"
94 :> Capture "node_id" NodeId
95 :> NodeAPI HyperdataAny
98 :<|> "corpus" :> Summary "Corpus endpoint"
99 :> Capture "corpus_id" CorpusId
100 :> NodeAPI HyperdataCorpus
102 :<|> "corpus" :> Summary "Corpus endpoint"
103 :> Capture "node1_id" NodeId
105 :> Capture "node2_id" NodeId
106 :> NodeNodeAPI HyperdataAny
108 :<|> "corpus" :> Capture "node_id" CorpusId
112 :<|> "annuaire" :> Summary "Annuaire endpoint"
113 :> Capture "annuaire_id" AnnuaireId
114 :> NodeAPI HyperdataAnnuaire
116 :<|> "annuaire" :> Summary "Contact endpoint"
117 :> Capture "annuaire_id" NodeId
121 :<|> "document" :> Summary "Document endpoint"
122 :> Capture "doc_id" DocId
123 :> "ngrams" :> TableNgramsApi
125 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
127 :<|> "count" :> Summary "Count endpoint"
128 :> ReqBody '[JSON] Query
131 -- Corpus endpoint --> TODO rename s/search/filter/g
132 -- :<|> "search" :> Capture "corpus" NodeId
133 -- :> (Search.API Search.SearchResult)
135 -- TODO move to NodeAPI?
136 :<|> "graph" :> Summary "Graph endpoint"
137 :> Capture "graph_id" NodeId
140 -- TODO move to NodeAPI?
142 :<|> "tree" :> Summary "Tree endpoint"
143 :> Capture "tree_id" NodeId
149 :<|> New.AddWithQuery
151 -- :<|> "annuaire" :> Annuaire.AddWithForm
152 -- :<|> New.AddWithFile
153 -- :<|> "scraper" :> WithCallbacks ScraperAPI
154 -- :<|> "new" :> New.Api
156 :<|> "lists" :> Summary "List export API"
157 :> Capture "listId" ListId
160 :<|> "wait" :> Summary "Wait test"
162 :> WaitAPI -- Get '[JSON] Int
168 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
169 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
170 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
171 ---------------------------------------------------------------------
173 type API = SwaggerAPI
177 -- | API for serving @swagger.json@
178 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
180 -- | API for serving main operational routes of @gargantext.org@
186 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
187 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
188 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
189 ---------------------------------------------------------------------
191 ---------------------------------------------------------------------
192 -- | Server declarations
194 -- TODO-SECURITY admin only: withAdmin
195 -- Question: How do we mark admins?
196 serverGargAdminAPI :: GargServer GargAdminAPI
197 serverGargAdminAPI = roots
201 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
202 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
204 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
205 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
206 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
207 :<|> Export.getCorpus -- uid
208 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
211 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
212 <$> PathNode <*> apiNgramsTableDoc
214 :<|> count -- TODO: undefined
216 -- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
217 -- <$> PathNode <*> Search.api -- TODO: move elsewhere
219 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
220 <$> PathNode <*> graphAPI uid -- TODO: mock
222 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
223 <$> PathNode <*> treeAPI
225 :<|> addCorpusWithForm (RootId (NodeId uid))
226 :<|> addCorpusWithFile (RootId (NodeId uid))
227 :<|> addCorpusWithQuery (RootId (NodeId uid))
229 -- :<|> addAnnuaireWithForm
230 -- :<|> New.api uid -- TODO-SECURITY
231 -- :<|> New.info uid -- TODO-SECURITY
236 ----------------------------------------------------------------------
238 type WaitAPI = Get '[JSON] Text
240 waitAPI :: Int -> GargServer WaitAPI
243 m = (10 :: Int) ^ (6 :: Int)
244 _ <- liftBase $ threadDelay ( m * n)
245 pure $ "Waited: " <> (cs $ show n)
246 ----------------------------------------
248 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
249 addCorpusWithQuery user cid = do
250 -- TODO gargantext.ini
251 -- _env <- view hasConfig
252 let limit = Just 10000
254 JobFunction (\q log ->
257 printDebug "addToCorpusWithQuery" x
259 in New.addToCorpusWithQuery user cid q limit log'
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))