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 ---------------------------------------------------------------------
27 import Control.Concurrent (threadDelay)
28 import Data.Text (Text)
31 import Servant.Auth as SA
32 import Servant.Auth.Swagger ()
33 import Servant.Job.Async
34 import Servant.Swagger.UI
36 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
37 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
38 import Gargantext.API.Prelude
39 import Gargantext.API.Count (CountAPI, count, Query)
40 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
41 import Gargantext.API.Node
42 import Gargantext.API.Search (SearchPairsAPI, searchPairs)
43 import Gargantext.Core.Types.Individu (User(..))
44 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
45 import Gargantext.Database.Admin.Types.Hyperdata
46 import Gargantext.Database.Admin.Types.Node
47 import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
48 import Gargantext.Prelude
49 import Gargantext.Viz.Graph.API
50 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
51 import qualified Gargantext.API.Node.Corpus.Export as Export
52 import qualified Gargantext.API.Node.Corpus.New as New
53 import qualified Gargantext.API.Ngrams.List as List
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.
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
120 :> Capture "contact_id" NodeId
121 :> NodeNodeAPI HyperdataContact
124 :<|> "document" :> Summary "Document endpoint"
125 :> Capture "doc_id" DocId
126 :> "ngrams" :> TableNgramsApi
128 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
130 :<|> "count" :> Summary "Count endpoint"
131 :> ReqBody '[JSON] Query
134 -- Corpus endpoint --> TODO rename s/search/filter/g
135 :<|> "search" :> Capture "corpus" NodeId
138 -- TODO move to NodeAPI?
139 :<|> "graph" :> Summary "Graph endpoint"
140 :> Capture "graph_id" NodeId
143 -- TODO move to NodeAPI?
145 :<|> "tree" :> Summary "Tree endpoint"
146 :> 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
211 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
213 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
214 <$> PathNode <*> apiNgramsTableDoc
216 :<|> count -- TODO: undefined
218 :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
219 <$> PathNode <*> searchPairs -- 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 (UserDBId uid)
228 :<|> addCorpusWithQuery (RootId (NodeId uid))
230 -- :<|> addAnnuaireWithForm
231 -- :<|> New.api uid -- TODO-SECURITY
232 -- :<|> New.info uid -- TODO-SECURITY
237 ----------------------------------------------------------------------
239 type WaitAPI = Get '[JSON] Text
241 waitAPI :: Int -> GargServer WaitAPI
244 m = (10 :: Int) ^ (6 :: Int)
245 _ <- liftBase $ threadDelay ( m * n)
246 pure $ "Waited: " <> (cs $ show n)
247 ----------------------------------------
250 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
251 addCorpusWithQuery user cid =
253 JobFunction (\q log ->
256 printDebug "addToCorpusWithQuery" x
258 in New.addToCorpusWithQuery user cid q log'
262 addWithFile :: GargServer New.AddWithFile
263 addWithFile cid i f =
265 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
268 addCorpusWithForm :: User -> GargServer New.AddWithForm
269 addCorpusWithForm user cid =
271 JobFunction (\i log ->
274 printDebug "addToCorpusWithForm" x
276 in New.addToCorpusWithForm user cid i log')
278 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
279 addAnnuaireWithForm cid =
281 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))