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 NoImplicitPrelude #-}
17 {-# LANGUAGE DataKinds #-}
18 {-# LANGUAGE DeriveGeneric #-}
19 {-# LANGUAGE FlexibleContexts #-}
20 {-# LANGUAGE FlexibleInstances #-}
21 {-# LANGUAGE OverloadedStrings #-}
22 {-# LANGUAGE TemplateHaskell #-}
23 {-# LANGUAGE TypeOperators #-}
24 {-# LANGUAGE KindSignatures #-}
25 {-# LANGUAGE RankNTypes #-}
26 {-# LANGUAGE ScopedTypeVariables #-}
27 {-# LANGUAGE TypeFamilies #-}
28 {-# LANGUAGE UndecidableInstances #-}
30 ---------------------------------------------------------------------
31 module Gargantext.API.Routes
33 ---------------------------------------------------------------------
34 import Control.Concurrent (threadDelay)
35 import Data.Text (Text)
37 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), withAccess, PathId(..))
38 import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
39 import Gargantext.API.Prelude
40 import Gargantext.API.Count (CountAPI, count, Query)
41 import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc)
42 import Gargantext.API.Node
43 import Gargantext.API.Search (SearchPairsAPI, searchPairs)
44 import Gargantext.Core.Types.Individu (User(..))
45 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
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
51 import Servant.Auth as SA
52 import Servant.Auth.Swagger ()
53 import Servant.Job.Async
54 import Servant.Swagger.UI
55 import qualified Gargantext.API.Node.Corpus.Annuaire as Annuaire
56 import qualified Gargantext.API.Node.Corpus.Export as Export
57 import qualified Gargantext.API.Node.Corpus.New as New
58 import qualified Gargantext.API.Ngrams.List as List
62 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
63 -- | TODO :<|> Summary "Latest API" :> GargAPI'
66 type GargAPIVersion = "v1.0"
67 :> Summary "Garg API Version "
70 type GargVersion = "version"
71 :> Summary "Backend version"
76 "auth" :> Summary "AUTH API"
77 :> ReqBody '[JSON] AuthRequest
78 :> Post '[JSON] AuthResponse
80 -- TODO-ACCESS here we want to request a particular header for
81 -- auth and capabilities.
85 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> GargPrivateAPI'
89 = "user" :> Summary "First user endpoint"
91 :<|> "nodes" :> Summary "Nodes endpoint"
92 :> ReqBody '[JSON] [NodeId] :> NodesAPI
94 type GargPrivateAPI' =
98 :<|> "node" :> Summary "Node endpoint"
99 :> Capture "node_id" NodeId
100 :> NodeAPI HyperdataAny
103 :<|> "corpus" :> Summary "Corpus endpoint"
104 :> Capture "corpus_id" CorpusId
105 :> NodeAPI HyperdataCorpus
107 :<|> "corpus" :> Summary "Corpus endpoint"
108 :> Capture "node1_id" NodeId
110 :> Capture "node2_id" NodeId
111 :> NodeNodeAPI HyperdataAny
113 :<|> "corpus" :> Capture "node_id" CorpusId
117 :<|> "annuaire" :> Summary "Annuaire endpoint"
118 :> Capture "annuaire_id" AnnuaireId
119 :> NodeAPI HyperdataAnnuaire
121 :<|> "annuaire" :> Summary "Contact endpoint"
122 :> Capture "annuaire_id" NodeId
124 :> Capture "contact_id" NodeId
125 :> NodeNodeAPI HyperdataContact
128 :<|> "document" :> Summary "Document endpoint"
129 :> Capture "doc_id" DocId
130 :> "ngrams" :> TableNgramsApi
132 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
134 :<|> "count" :> Summary "Count endpoint"
135 :> ReqBody '[JSON] Query
138 -- Corpus endpoint --> TODO rename s/search/filter/g
139 :<|> "search" :> Capture "corpus" NodeId
142 -- TODO move to NodeAPI?
143 :<|> "graph" :> Summary "Graph endpoint"
144 :> Capture "graph_id" NodeId
147 -- TODO move to NodeAPI?
149 :<|> "tree" :> Summary "Tree endpoint"
150 :> Capture "tree_id" NodeId
155 :<|> New.AddWithQuery
157 -- :<|> "annuaire" :> Annuaire.AddWithForm
158 -- :<|> New.AddWithFile
159 -- :<|> "scraper" :> WithCallbacks ScraperAPI
160 -- :<|> "new" :> New.Api
162 :<|> "lists" :> Summary "List export API"
163 :> Capture "listId" ListId
166 :<|> "wait" :> Summary "Wait test"
168 :> WaitAPI -- Get '[JSON] Int
174 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
175 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
176 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
177 ---------------------------------------------------------------------
179 type API = SwaggerAPI
183 -- | API for serving @swagger.json@
184 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
186 -- | API for serving main operational routes of @gargantext.org@
192 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
193 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
194 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
195 ---------------------------------------------------------------------
197 ---------------------------------------------------------------------
198 -- | Server declarations
200 -- TODO-SECURITY admin only: withAdmin
201 -- Question: How do we mark admins?
202 serverGargAdminAPI :: GargServer GargAdminAPI
203 serverGargAdminAPI = roots
207 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
208 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
210 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
211 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
212 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
213 :<|> Export.getCorpus -- uid
214 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
215 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
217 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
218 <$> PathNode <*> apiNgramsTableDoc
220 :<|> count -- TODO: undefined
222 :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
223 <$> PathNode <*> searchPairs -- TODO: move elsewhere
225 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
226 <$> PathNode <*> graphAPI uid -- TODO: mock
228 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
229 <$> PathNode <*> treeAPI
231 :<|> addCorpusWithForm (UserDBId uid)
232 :<|> addCorpusWithQuery (RootId (NodeId uid))
234 -- :<|> addAnnuaireWithForm
235 -- :<|> New.api uid -- TODO-SECURITY
236 -- :<|> New.info uid -- TODO-SECURITY
241 ----------------------------------------------------------------------
243 type WaitAPI = Get '[JSON] Text
245 waitAPI :: Int -> GargServer WaitAPI
248 m = (10 :: Int) ^ (6 :: Int)
249 _ <- liftBase $ threadDelay ( m * n)
250 pure $ "Waited: " <> (cs $ show n)
251 ----------------------------------------
254 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
255 addCorpusWithQuery user cid =
257 JobFunction (\q log ->
260 printDebug "addToCorpusWithQuery" x
262 in New.addToCorpusWithQuery user cid q log'
266 addWithFile :: GargServer New.AddWithFile
267 addWithFile cid i f =
269 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
272 addCorpusWithForm :: User -> GargServer New.AddWithForm
273 addCorpusWithForm user cid =
275 JobFunction (\i log ->
278 printDebug "addToCorpusWithForm" x
280 in New.addToCorpusWithForm user cid i log')
282 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
283 addAnnuaireWithForm cid =
285 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))