2 Module : Gargantext.API.Routes
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
13 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
15 {-# LANGUAGE ConstraintKinds #-}
16 {-# LANGUAGE TemplateHaskell #-}
17 {-# LANGUAGE TypeOperators #-}
18 {-# LANGUAGE KindSignatures #-}
19 {-# LANGUAGE ScopedTypeVariables #-}
20 {-# LANGUAGE TypeFamilies #-}
21 {-# LANGUAGE UndecidableInstances #-}
23 ---------------------------------------------------------------------
24 module Gargantext.API.Routes
26 ---------------------------------------------------------------------
28 import Control.Concurrent (threadDelay)
29 import Data.Text (Text)
31 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
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.API.Search (SearchPairsAPI, searchPairs)
38 import Gargantext.Core.Types.Individu (User(..))
39 import Gargantext.Database.Admin.Types.Hyperdata
40 import Gargantext.Database.Admin.Types.Node
41 import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
42 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
43 import Gargantext.Prelude
44 import Gargantext.Viz.Graph.API
46 import Servant.Auth as SA
47 import Servant.Auth.Swagger ()
48 import Servant.Job.Async
49 import Servant.Swagger.UI
50 import qualified Gargantext.API.Ngrams.List as List
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
57 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
58 -- | TODO :<|> Summary "Latest API" :> GargAPI'
61 type GargAPIVersion = "v1.0"
62 :> Summary "Garg API Version "
65 type GargVersion = "version"
66 :> Summary "Backend version"
71 "auth" :> Summary "AUTH API"
72 :> ReqBody '[JSON] AuthRequest
73 :> Post '[JSON] AuthResponse
75 -- TODO-ACCESS here we want to request a particular header for
76 -- auth and capabilities.
78 :<|> "public" :> Public.API
81 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
86 = "user" :> Summary "First user endpoint"
88 :<|> "nodes" :> Summary "Nodes endpoint"
89 :> ReqBody '[JSON] [NodeId] :> NodesAPI
91 type GargPrivateAPI' =
95 :<|> "node" :> Summary "Node endpoint"
96 :> Capture "node_id" NodeId
97 :> NodeAPI HyperdataAny
100 :<|> "corpus" :> Summary "Corpus endpoint"
101 :> Capture "corpus_id" CorpusId
102 :> NodeAPI HyperdataCorpus
104 :<|> "corpus" :> Summary "Corpus endpoint"
105 :> Capture "node1_id" NodeId
107 :> Capture "node2_id" NodeId
108 :> NodeNodeAPI HyperdataAny
110 :<|> "corpus" :> Capture "node_id" CorpusId
114 :<|> "annuaire" :> Summary "Annuaire endpoint"
115 :> Capture "annuaire_id" AnnuaireId
116 :> NodeAPI HyperdataAnnuaire
118 :<|> "annuaire" :> Summary "Contact endpoint"
119 :> Capture "annuaire_id" NodeId
121 :> Capture "contact_id" NodeId
122 :> NodeNodeAPI HyperdataContact
125 :<|> "document" :> Summary "Document endpoint"
126 :> Capture "doc_id" DocId
127 :> "ngrams" :> TableNgramsApi
129 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
131 :<|> "count" :> Summary "Count endpoint"
132 :> ReqBody '[JSON] Query
135 -- Corpus endpoint --> TODO rename s/search/filter/g
136 :<|> "search" :> Capture "corpus" NodeId
139 -- TODO move to NodeAPI?
140 :<|> "graph" :> Summary "Graph endpoint"
141 :> Capture "graph_id" NodeId
144 -- TODO move to NodeAPI?
146 :<|> "tree" :> Summary "Tree endpoint"
147 :> Capture "tree_id" NodeId
152 :<|> New.AddWithQuery
154 -- :<|> "annuaire" :> Annuaire.AddWithForm
155 -- :<|> New.AddWithFile
156 -- :<|> "scraper" :> WithCallbacks ScraperAPI
157 -- :<|> "new" :> New.Api
159 :<|> "lists" :> Summary "List export API"
160 :> Capture "listId" ListId
163 :<|> "wait" :> Summary "Wait test"
165 :> WaitAPI -- Get '[JSON] Int
171 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
172 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
173 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
174 ---------------------------------------------------------------------
176 type API = SwaggerAPI
180 -- | API for serving @swagger.json@
181 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
183 -- | API for serving main operational routes of @gargantext.org@
189 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
190 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
191 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
192 ---------------------------------------------------------------------
194 ---------------------------------------------------------------------
195 -- | Server declarations
197 -- TODO-SECURITY admin only: withAdmin
198 -- Question: How do we mark admins?
199 serverGargAdminAPI :: GargServer GargAdminAPI
200 serverGargAdminAPI = roots
204 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
205 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
207 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
208 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
209 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
210 :<|> Export.getCorpus -- uid
211 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
212 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
214 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
215 <$> PathNode <*> apiNgramsTableDoc
217 :<|> count -- TODO: undefined
219 :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
220 <$> PathNode <*> searchPairs -- TODO: move elsewhere
222 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
223 <$> PathNode <*> graphAPI uid -- TODO: mock
225 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
226 <$> PathNode <*> treeAPI
228 :<|> addCorpusWithForm (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 ----------------------------------------
251 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
252 addCorpusWithQuery user cid =
254 JobFunction (\q log ->
257 printDebug "addToCorpusWithQuery" x
259 in New.addToCorpusWithQuery user cid q 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 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
280 addAnnuaireWithForm cid =
282 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))