2 Module : Gargantext.API
3 Description : REST API declaration
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Main (RESTful) API of the instance Gargantext.
12 The Garg-API is typed to derive the documentation, the mock and tests.
14 This API is indeed typed in order to be able to derive both the server
17 The Garg-API-Monad enables:
20 - Database connection (long term)
21 - In Memory stack management (short term)
24 Thanks to Yann Esposito for our discussions at the start and to Nicolas
25 Pouillard (who mainly made it).
29 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
31 {-# LANGUAGE ConstraintKinds #-}
32 {-# LANGUAGE NoImplicitPrelude #-}
33 {-# LANGUAGE DataKinds #-}
34 {-# LANGUAGE DeriveGeneric #-}
35 {-# LANGUAGE FlexibleContexts #-}
36 {-# LANGUAGE FlexibleInstances #-}
37 {-# LANGUAGE OverloadedStrings #-}
38 {-# LANGUAGE TemplateHaskell #-}
39 {-# LANGUAGE TypeOperators #-}
40 {-# LANGUAGE KindSignatures #-}
41 {-# LANGUAGE RankNTypes #-}
42 {-# LANGUAGE ScopedTypeVariables #-}
43 {-# LANGUAGE TypeFamilies #-}
44 {-# LANGUAGE UndecidableInstances #-}
46 ---------------------------------------------------------------------
49 ---------------------------------------------------------------------
50 import Control.Concurrent (threadDelay)
51 import Control.Exception (finally)
53 import Control.Monad.Except (withExceptT, ExceptT)
54 import Control.Monad.Reader (ReaderT, runReaderT)
55 import Data.Aeson.Encode.Pretty (encodePretty)
56 import Data.List (lookup)
58 import Data.Text (Text)
59 import Data.Text.Encoding (encodeUtf8)
61 import Data.Version (showVersion)
62 import GHC.Base (Applicative)
63 import GHC.Generics (D1, Meta (..), Rep)
64 import GHC.TypeLits (AppendSymbol, Symbol)
65 import Gargantext.API.Admin.Auth (AuthRequest, AuthResponse, AuthenticatedUser(..), AuthContext, auth, withAccess, PathId(..))
66 import Gargantext.API.Admin.FrontEnd (FrontEndAPI, frontEndServer)
67 import Gargantext.API.Admin.Orchestrator.Types
68 import Gargantext.API.Admin.Settings
69 import Gargantext.API.Admin.Types
70 import Gargantext.API.Count ( CountAPI, count, Query)
71 import Gargantext.API.Ngrams (HasRepo(..), HasRepoSaver(..), saveRepo, TableNgramsApi, apiNgramsTableDoc)
72 import Gargantext.API.Node
73 import Gargantext.API.Search (SearchPairsAPI, searchPairs)
74 import Gargantext.Core.Types.Individu (User(..))
75 import Gargantext.Database.Query.Table.Node.Contact (HyperdataContact)
76 import Gargantext.Database.Admin.Types.Node
77 import Gargantext.Database.Admin.Types.Node (NodeId, CorpusId, AnnuaireId)
78 import Gargantext.Database.Admin.Utils (HasConnectionPool)
79 import Gargantext.Prelude
80 import Gargantext.Viz.Graph.API
81 import Network.HTTP.Types hiding (Query)
83 import Network.Wai (Request, requestHeaders)
84 import Network.Wai.Handler.Warp hiding (defaultSettings)
85 import Network.Wai.Middleware.Cors
86 import Network.Wai.Middleware.RequestLogger
88 import Servant.Auth as SA
89 import Servant.Auth.Server (AuthResult(..))
90 import Servant.Auth.Swagger ()
91 import Servant.Job.Async
92 import Servant.Swagger
93 import Servant.Swagger.UI
94 import System.IO (FilePath)
95 import qualified Data.ByteString.Lazy.Char8 as BL8
96 import qualified Data.Text.IO as T
97 import qualified Gargantext.API.Corpus.Annuaire as Annuaire
98 import qualified Gargantext.API.Corpus.Export as Export
99 import qualified Gargantext.API.Corpus.New as New
100 import qualified Gargantext.API.Ngrams.List as List
101 import qualified Paths_gargantext as PG -- cabal magic build module
103 showAsServantErr :: GargError -> ServerError
104 showAsServantErr (GargServerError err) = err
105 showAsServantErr a = err500 { errBody = BL8.pack $ show a }
107 fireWall :: Applicative f => Request -> FireWall -> f Bool
109 let origin = lookup "Origin" (requestHeaders req)
110 let host = lookup "Host" (requestHeaders req)
112 let hostOk = Just (encodeUtf8 "localhost:3000")
113 let originOk = Just (encodeUtf8 "http://localhost:8008")
115 if origin == originOk
117 || (not $ unFireWall fw)
123 -- makeMockApp :: Env -> IO (Warp.Settings, Application)
124 makeMockApp :: MockEnv -> IO Application
126 let serverApp = appMock
128 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
129 --logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
130 let checkOriginAndHost app req resp = do
131 blocking <- fireWall req (env ^. menv_firewall)
134 False -> resp ( responseLBS status401 []
135 "Invalid Origin or Host header")
137 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
138 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
139 { corsOrigins = Nothing -- == /*
140 , corsMethods = [ methodGet , methodPost , methodPut
141 , methodDelete, methodOptions, methodHead]
142 , corsRequestHeaders = ["authorization", "content-type"]
143 , corsExposedHeaders = Nothing
144 , corsMaxAge = Just ( 60*60*24 ) -- one day
145 , corsVaryOrigin = False
146 , corsRequireOrigin = False
147 , corsIgnoreFailures = False
150 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
151 -- $ Warp.defaultSettings
153 --pure (warpS, logWare $ checkOriginAndHost $ corsMiddleware $ serverApp)
154 pure $ logStdoutDev $ checkOriginAndHost $ corsMiddleware $ serverApp
158 makeDevMiddleware :: IO Middleware
159 makeDevMiddleware = do
161 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
162 --logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
163 -- let checkOriginAndHost app req resp = do
164 -- blocking <- fireWall req (env ^. menv_firewall)
166 -- True -> app req resp
167 -- False -> resp ( responseLBS status401 []
168 -- "Invalid Origin or Host header")
170 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
171 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
172 { corsOrigins = Nothing -- == /*
173 , corsMethods = [ methodGet , methodPost , methodPut
174 , methodDelete, methodOptions, methodHead]
175 , corsRequestHeaders = ["authorization", "content-type"]
176 , corsExposedHeaders = Nothing
177 , corsMaxAge = Just ( 60*60*24 ) -- one day
178 , corsVaryOrigin = False
179 , corsRequireOrigin = False
180 , corsIgnoreFailures = False
183 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
184 -- $ Warp.defaultSettings
186 --pure (warpS, logWare . checkOriginAndHost . corsMiddleware)
187 pure $ logStdoutDev . corsMiddleware
189 ---------------------------------------------------------------------
192 -- | API for serving @swagger.json@
193 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
195 -- | API for serving main operational routes of @gargantext.org@
198 type GargAPI = "api" :> Summary "API " :> GargAPIVersion
199 -- | TODO :<|> Summary "Latest API" :> GargAPI'
202 type GargAPIVersion = "v1.0"
203 :> Summary "Garg API Version "
206 type GargVersion = "version"
207 :> Summary "Backend version"
212 "auth" :> Summary "AUTH API"
213 :> ReqBody '[JSON] AuthRequest
214 :> Post '[JSON] AuthResponse
216 -- TODO-ACCESS here we want to request a particular header for
217 -- auth and capabilities.
221 type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> GargPrivateAPI'
225 = "user" :> Summary "First user endpoint"
227 :<|> "nodes" :> Summary "Nodes endpoint"
228 :> ReqBody '[JSON] [NodeId] :> NodesAPI
230 ----------------------------------------
232 type WaitAPI = Get '[JSON] Text
234 waitAPI :: Int -> GargServer WaitAPI
237 m = (10 :: Int) ^ (6 :: Int)
238 _ <- liftBase $ threadDelay ( m * n)
239 pure $ "Waited: " <> (cs $ show n)
240 ----------------------------------------
243 type GargPrivateAPI' =
247 :<|> "node" :> Summary "Node endpoint"
248 :> Capture "node_id" NodeId
249 :> NodeAPI HyperdataAny
252 :<|> "corpus" :> Summary "Corpus endpoint"
253 :> Capture "corpus_id" CorpusId
254 :> NodeAPI HyperdataCorpus
256 :<|> "corpus" :> Summary "Corpus endpoint"
257 :> Capture "node1_id" NodeId
259 :> Capture "node2_id" NodeId
260 :> NodeNodeAPI HyperdataAny
262 :<|> "corpus" :> Capture "node_id" CorpusId
266 :<|> "annuaire" :> Summary "Annuaire endpoint"
267 :> Capture "annuaire_id" AnnuaireId
268 :> NodeAPI HyperdataAnnuaire
270 :<|> "annuaire" :> Summary "Contact endpoint"
271 :> Capture "annuaire_id" NodeId
273 :> Capture "contact_id" NodeId
274 :> NodeNodeAPI HyperdataContact
277 :<|> "document" :> Summary "Document endpoint"
278 :> Capture "doc_id" DocId
279 :> "ngrams" :> TableNgramsApi
281 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
283 :<|> "count" :> Summary "Count endpoint"
284 :> ReqBody '[JSON] Query
287 -- Corpus endpoint --> TODO rename s/search/filter/g
288 :<|> "search" :> Capture "corpus" NodeId
291 -- TODO move to NodeAPI?
292 :<|> "graph" :> Summary "Graph endpoint"
293 :> Capture "graph_id" NodeId
296 -- TODO move to NodeAPI?
298 :<|> "tree" :> Summary "Tree endpoint"
299 :> Capture "tree_id" NodeId
304 :<|> New.AddWithQuery
306 -- :<|> "annuaire" :> Annuaire.AddWithForm
307 -- :<|> New.AddWithFile
308 -- :<|> "scraper" :> WithCallbacks ScraperAPI
309 -- :<|> "new" :> New.Api
311 :<|> "lists" :> Summary "List export API"
312 :> Capture "listId" ListId
315 :<|> "wait" :> Summary "Wait test"
317 :> WaitAPI -- Get '[JSON] Int
323 -- :<|> "list" :> Capture "node_id" Int :> NodeAPI
324 -- :<|> "ngrams" :> Capture "node_id" Int :> NodeAPI
325 -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
326 ---------------------------------------------------------------------
328 type API = SwaggerAPI
332 -- This is the concrete monad. It needs to be used as little as possible,
333 -- instead, prefer GargServer, GargServerT, GargServerC.
334 type GargServerM env err = ReaderT env (ExceptT err IO)
337 ( HasConnectionPool env
340 , HasJobEnv env ScraperStatus ScraperStatus
343 ---------------------------------------------------------------------
344 -- | Server declarations
346 server :: forall env. EnvC env => env -> IO (Server API)
348 -- orchestrator <- scrapyOrchestrator env
349 pure $ schemaUiServer swaggerDoc
350 :<|> hoistServerWithContext
351 (Proxy :: Proxy GargAPI)
352 (Proxy :: Proxy AuthContext)
357 transform :: forall a. GargServerM env GargError a -> Handler a
358 transform = Handler . withExceptT showAsServantErr . (`runReaderT` env)
360 serverGargAPI :: GargServerT env err (GargServerM env err) GargAPI
361 serverGargAPI -- orchestrator
364 :<|> serverPrivateGargAPI
368 gargVersion :: GargServer GargVersion
369 gargVersion = pure (cs $ showVersion PG.version)
371 serverPrivateGargAPI :: GargServerT env err (GargServerM env err) GargPrivateAPI
372 serverPrivateGargAPI (Authenticated auser) = serverPrivateGargAPI' auser
373 serverPrivateGargAPI _ = throwAll' (_ServerError # err401)
374 -- Here throwAll' requires a concrete type for the monad.
376 -- TODO-SECURITY admin only: withAdmin
377 -- Question: How do we mark admins?
378 serverGargAdminAPI :: GargServer GargAdminAPI
379 serverGargAdminAPI = roots
383 serverPrivateGargAPI' :: AuthenticatedUser -> GargServer GargPrivateAPI'
384 serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
386 :<|> nodeAPI (Proxy :: Proxy HyperdataAny) uid
387 :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
388 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
389 :<|> Export.getCorpus -- uid
390 :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
391 :<|> nodeNodeAPI (Proxy :: Proxy HyperdataContact) uid
393 :<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy uid
394 <$> PathNode <*> apiNgramsTableDoc
396 :<|> count -- TODO: undefined
398 :<|> withAccess (Proxy :: Proxy SearchPairsAPI) Proxy uid
399 <$> PathNode <*> searchPairs -- TODO: move elsewhere
401 :<|> withAccess (Proxy :: Proxy GraphAPI) Proxy uid
402 <$> PathNode <*> graphAPI uid -- TODO: mock
404 :<|> withAccess (Proxy :: Proxy TreeAPI) Proxy uid
405 <$> PathNode <*> treeAPI
407 :<|> addCorpusWithForm (UserDBId uid)
408 :<|> addCorpusWithQuery (RootId (NodeId uid))
410 -- :<|> addAnnuaireWithForm
411 -- :<|> New.api uid -- TODO-SECURITY
412 -- :<|> New.info uid -- TODO-SECURITY
417 addCorpusWithQuery :: User -> GargServer New.AddWithQuery
418 addCorpusWithQuery user cid =
420 JobFunction (\q log ->
423 printDebug "addToCorpusWithQuery" x
425 in New.addToCorpusWithQuery user cid q log'
429 addWithFile :: GargServer New.AddWithFile
430 addWithFile cid i f =
432 JobFunction (\_i log -> New.addToCorpusWithFile cid i f (liftBase . log))
435 addCorpusWithForm :: User -> GargServer New.AddWithForm
436 addCorpusWithForm user cid =
438 JobFunction (\i log ->
441 printDebug "addToCorpusWithForm" x
443 in New.addToCorpusWithForm user cid i log')
445 addAnnuaireWithForm :: GargServer Annuaire.AddWithForm
446 addAnnuaireWithForm cid =
448 JobFunction (\i log -> Annuaire.addToAnnuaireWithForm cid i (liftBase . log))
451 serverStatic :: Server (Get '[HTML] Html)
453 let path = "purescript-gargantext/dist/index.html"
454 Just s <- liftBase (fileTypeToFileTree (FileTypeFile path))
458 ---------------------------------------------------------------------
459 --gargMock :: Server GargAPI
460 --gargMock = mock apiGarg Proxy
461 ---------------------------------------------------------------------
462 makeApp :: EnvC env => env -> IO Application
463 makeApp env = serveWithContext api cfg <$> server env
465 cfg :: Servant.Context AuthContext
466 cfg = env ^. settings . jwtSettings
467 :. env ^. settings . cookieSettings
471 --appMock :: Application
472 --appMock = serve api (swaggerFront :<|> gargMock :<|> serverStatic)
473 ---------------------------------------------------------------------
477 apiGarg :: Proxy GargAPI
479 ---------------------------------------------------------------------
480 schemaUiServer :: (Server api ~ Handler Swagger)
481 => Swagger -> Server (SwaggerSchemaUI' dir api)
482 schemaUiServer = swaggerSchemaUIServer
484 -- Type Family for the Documentation
485 type family TypeName (x :: *) :: Symbol where
487 TypeName Text = "Text"
488 TypeName x = GenericTypeName x (Rep x ())
490 type family GenericTypeName t (r :: *) :: Symbol where
491 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
493 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
496 -- | Swagger Specifications
497 swaggerDoc :: Swagger
498 swaggerDoc = toSwagger (Proxy :: Proxy GargAPI)
499 & info.title .~ "Gargantext"
500 & info.version .~ (cs $ showVersion PG.version)
501 -- & info.base_url ?~ (URL "http://gargantext.org/")
502 & info.description ?~ "REST API specifications"
503 -- & tags .~ Set.fromList [Tag "Garg" (Just "Main perations") Nothing]
504 & applyTagsFor (subOperations (Proxy :: Proxy GargAPI)(Proxy :: Proxy GargAPI))
505 ["Gargantext" & description ?~ "Main operations"]
506 & info.license ?~ ("AGPLV3 (English) and CECILL (French)" & url ?~ URL urlLicence )
508 urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
510 -- | Output generated @swagger.json@ file for the @'TodoAPI'@.
511 swaggerWriteJSON :: IO ()
512 swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
514 portRouteInfo :: PortNumber -> IO ()
515 portRouteInfo port = do
516 T.putStrLn " ----Main Routes----- "
517 T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/index.html"
518 T.putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui"
520 stopGargantext :: HasRepoSaver env => env -> IO ()
521 stopGargantext env = do
522 T.putStrLn "----- Stopping gargantext -----"
523 runReaderT saveRepo env
525 -- | startGargantext takes as parameters port number and Ini file.
526 startGargantext :: PortNumber -> FilePath -> IO ()
527 startGargantext port file = do
528 env <- newEnv port file
531 mid <- makeDevMiddleware
532 run port (mid app) `finally` stopGargantext env
535 startGargantextMock :: PortNumber -> IO ()
536 startGargantextMock port = do
538 application <- makeMockApp . MockEnv $ FireWall False