2 Module : Gargantext.API.Server
3 Description : REST API declaration
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
11 {-# LANGUAGE MonoLocalBinds #-}
12 {-# LANGUAGE ScopedTypeVariables #-}
14 ---------------------------------------------------------------------
15 module Gargantext.API.Server where
16 ---------------------------------------------------------------------
17 import Control.Lens ((^.))
18 import Control.Monad.Except (withExceptT)
19 import Control.Monad.Reader (runReaderT)
21 import Data.Text (Text)
22 import Data.Version (showVersion)
24 import Servant.Swagger.UI (swaggerSchemaUIServer)
25 import qualified Data.ByteString.Lazy.Char8 as BL8
26 import qualified Paths_gargantext as PG -- cabal magic build module
28 import qualified Gargantext.API.Public as Public
30 import Gargantext.API.Admin.Auth.Types (AuthContext)
31 import Gargantext.API.Admin.Auth (auth)
32 import Gargantext.API.Admin.FrontEnd (frontEndServer)
33 import Gargantext.API.Prelude
34 import Gargantext.API.Routes
35 import Gargantext.API.Swagger (swaggerDoc)
36 import Gargantext.API.ThrowAll (serverPrivateGargAPI)
37 import Gargantext.Database.Query.Table.Node.Error (NodeError(..))
38 import Gargantext.Database.Prelude (hasConfig)
39 import Gargantext.Prelude
40 import Gargantext.Prelude.Config (gc_url_backend_api)
43 serverGargAPI :: ToJSON err => Text -> GargServerM env err GargAPI
44 serverGargAPI baseUrl -- orchestrator
47 :<|> serverPrivateGargAPI
48 :<|> Public.api baseUrl
52 gargVersion :: GargServer GargVersion
53 gargVersion = pure (cs $ showVersion PG.version)
55 -- | Server declarations
56 server :: forall env. EnvC env => env -> IO (Server API)
58 -- orchestrator <- scrapyOrchestrator env
59 pure $ swaggerSchemaUIServer swaggerDoc
60 :<|> hoistServerWithContext
61 (Proxy :: Proxy GargAPI)
62 (Proxy :: Proxy AuthContext)
64 (serverGargAPI (env ^. hasConfig . gc_url_backend_api))
67 transform :: forall a. GargM env GargError a -> Handler a
68 transform = Handler . withExceptT showAsServantErr . (`runReaderT` env)
71 showAsServantErr :: GargError -> ServerError
72 showAsServantErr (GargNodeError err@NoListFound) = err404 { errBody = BL8.pack $ show err }
73 showAsServantErr (GargNodeError err@NoRootFound) = err404 { errBody = BL8.pack $ show err }
74 showAsServantErr (GargNodeError err@NoCorpusFound) = err404 { errBody = BL8.pack $ show err }
75 showAsServantErr (GargNodeError err@NoUserFound) = err404 { errBody = BL8.pack $ show err }
76 showAsServantErr (GargNodeError err@(DoesNotExist _)) = err404 { errBody = BL8.pack $ show err }
77 showAsServantErr (GargServerError err) = err
78 showAsServantErr a = err500 { errBody = BL8.pack $ show a }