{-# LANGUAGE QuasiQuotes #-}
{-# OPTIONS_GHC -O0 #-}
module Hasura.Server.Init
(
mkHGEOptions,
mkServeOptions,
processPostgresConnInfo,
getDbId,
getPgVersion,
module Hasura.Server.Init.Config,
module Hasura.Server.Init.Env,
module Hasura.Server.Init.Arg,
module Hasura.Server.Init.Logging,
)
where
import Data.HashSet qualified as HashSet
import Data.Text qualified as Text
import Database.PG.Query qualified as Query
import Hasura.Backends.Postgres.Connection qualified as Connection
import Hasura.Base.Error qualified as Error
import Hasura.GraphQL.Execute.Subscription.Options qualified as Subscription.Options
import Hasura.GraphQL.Schema.Options qualified as Options
import Hasura.Logging qualified as Logging
import Hasura.Prelude
import Hasura.RQL.Types.Common qualified as Common
import Hasura.RQL.Types.Numeric qualified as Numeric
import Hasura.Server.Auth qualified as Auth
import Hasura.Server.Cors qualified as Cors
import Hasura.Server.Init.Arg
import Hasura.Server.Init.Config
import Hasura.Server.Init.Env
import Hasura.Server.Init.Logging
import Hasura.Server.Logging qualified as Server.Logging
import Hasura.Server.Types qualified as Types
import Network.WebSockets qualified as WebSockets
getDbId :: Query.TxE Error.QErr Types.MetadataDbId
getDbId :: TxE QErr MetadataDbId
getDbId =
Text -> MetadataDbId
Types.MetadataDbId (Text -> MetadataDbId)
-> (SingleRow (Identity Text) -> Text)
-> SingleRow (Identity Text)
-> MetadataDbId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity Text -> Text
forall a. Identity a -> a
runIdentity (Identity Text -> Text)
-> (SingleRow (Identity Text) -> Identity Text)
-> SingleRow (Identity Text)
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SingleRow (Identity Text) -> Identity Text
forall a. SingleRow a -> a
Query.getRow
(SingleRow (Identity Text) -> MetadataDbId)
-> TxET QErr IO (SingleRow (Identity Text))
-> TxE QErr MetadataDbId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (PGTxErr -> QErr)
-> Query -> () -> Bool -> TxET QErr IO (SingleRow (Identity Text))
forall (m :: * -> *) a r e.
(MonadIO m, FromRes a, ToPrepArgs r) =>
(PGTxErr -> e) -> Query -> r -> Bool -> TxET e m a
Query.withQE
PGTxErr -> QErr
Connection.defaultTxErrorHandler
[Query.sql|
SELECT (hasura_uuid :: text) FROM hdb_catalog.hdb_version
|]
()
Bool
False
getPgVersion :: Query.TxE Error.QErr Types.PGVersion
getPgVersion :: TxE QErr PGVersion
getPgVersion = Int -> PGVersion
Types.PGVersion (Int -> PGVersion) -> TxET QErr IO Int -> TxE QErr PGVersion
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TxET QErr IO Int
forall (m :: * -> *) e. MonadIO m => TxET e m Int
Query.serverVersion
mkHGEOptions ::
Logging.EnabledLogTypes impl => HGEOptionsRaw (ServeOptionsRaw impl) -> WithEnv (HGEOptions (ServeOptions impl))
mkHGEOptions :: HGEOptionsRaw (ServeOptionsRaw impl)
-> WithEnv (HGEOptions (ServeOptions impl))
mkHGEOptions (HGEOptionsRaw PostgresConnInfo (Maybe PostgresConnInfoRaw)
rawDbUrl Maybe String
rawMetadataDbUrl HGECommand (ServeOptionsRaw impl)
rawCmd) = do
PostgresConnInfo (Maybe UrlConf)
dbUrl <- PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> WithEnv (PostgresConnInfo (Maybe UrlConf))
processPostgresConnInfo PostgresConnInfo (Maybe PostgresConnInfoRaw)
rawDbUrl
Maybe String
metadataDbUrl <- Maybe String -> Option () -> WithEnvT Identity (Maybe String)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe String
rawMetadataDbUrl Option ()
metadataDbUrlOption
HGECommand (ServeOptions impl)
cmd <- case HGECommand (ServeOptionsRaw impl)
rawCmd of
HCServe ServeOptionsRaw impl
rso -> ServeOptions impl -> HGECommand (ServeOptions impl)
forall a. a -> HGECommand a
HCServe (ServeOptions impl -> HGECommand (ServeOptions impl))
-> WithEnvT Identity (ServeOptions impl)
-> WithEnvT Identity (HGECommand (ServeOptions impl))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ServeOptionsRaw impl -> WithEnvT Identity (ServeOptions impl)
forall impl.
EnabledLogTypes impl =>
ServeOptionsRaw impl -> WithEnv (ServeOptions impl)
mkServeOptions ServeOptionsRaw impl
rso
HGECommand (ServeOptionsRaw impl)
HCExport -> HGECommand (ServeOptions impl)
-> WithEnvT Identity (HGECommand (ServeOptions impl))
forall (f :: * -> *) a. Applicative f => a -> f a
pure HGECommand (ServeOptions impl)
forall a. HGECommand a
HCExport
HGECommand (ServeOptionsRaw impl)
HCClean -> HGECommand (ServeOptions impl)
-> WithEnvT Identity (HGECommand (ServeOptions impl))
forall (f :: * -> *) a. Applicative f => a -> f a
pure HGECommand (ServeOptions impl)
forall a. HGECommand a
HCClean
HGECommand (ServeOptionsRaw impl)
HCVersion -> HGECommand (ServeOptions impl)
-> WithEnvT Identity (HGECommand (ServeOptions impl))
forall (f :: * -> *) a. Applicative f => a -> f a
pure HGECommand (ServeOptions impl)
forall a. HGECommand a
HCVersion
HCDowngrade DowngradeOptions
tgt -> HGECommand (ServeOptions impl)
-> WithEnvT Identity (HGECommand (ServeOptions impl))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DowngradeOptions -> HGECommand (ServeOptions impl)
forall a. DowngradeOptions -> HGECommand a
HCDowngrade DowngradeOptions
tgt)
HGEOptions (ServeOptions impl)
-> WithEnv (HGEOptions (ServeOptions impl))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HGEOptions (ServeOptions impl)
-> WithEnv (HGEOptions (ServeOptions impl)))
-> HGEOptions (ServeOptions impl)
-> WithEnv (HGEOptions (ServeOptions impl))
forall a b. (a -> b) -> a -> b
$ PostgresConnInfo (Maybe UrlConf)
-> Maybe String
-> HGECommand (ServeOptions impl)
-> HGEOptions (ServeOptions impl)
forall impl.
PostgresConnInfo (Maybe UrlConf)
-> Maybe String -> HGECommand impl -> HGEOptions impl
HGEOptions PostgresConnInfo (Maybe UrlConf)
dbUrl Maybe String
metadataDbUrl HGECommand (ServeOptions impl)
cmd
processPostgresConnInfo ::
PostgresConnInfo (Maybe PostgresConnInfoRaw) ->
WithEnv (PostgresConnInfo (Maybe Common.UrlConf))
processPostgresConnInfo :: PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> WithEnv (PostgresConnInfo (Maybe UrlConf))
processPostgresConnInfo PostgresConnInfo {Maybe Int
Maybe PostgresConnInfoRaw
_pciRetries :: forall a. PostgresConnInfo a -> Maybe Int
_pciDatabaseConn :: forall a. PostgresConnInfo a -> a
_pciRetries :: Maybe Int
_pciDatabaseConn :: Maybe PostgresConnInfoRaw
..} = do
Maybe Int
withEnvRetries <- Maybe Int -> Option () -> WithEnvT Identity (Maybe Int)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe Int
_pciRetries Option ()
retriesNumOption
Maybe UrlConf
databaseUrl <- Maybe PostgresConnInfoRaw -> WithEnv (Maybe UrlConf)
rawConnInfoToUrlConf Maybe PostgresConnInfoRaw
_pciDatabaseConn
PostgresConnInfo (Maybe UrlConf)
-> WithEnv (PostgresConnInfo (Maybe UrlConf))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PostgresConnInfo (Maybe UrlConf)
-> WithEnv (PostgresConnInfo (Maybe UrlConf)))
-> PostgresConnInfo (Maybe UrlConf)
-> WithEnv (PostgresConnInfo (Maybe UrlConf))
forall a b. (a -> b) -> a -> b
$ Maybe UrlConf -> Maybe Int -> PostgresConnInfo (Maybe UrlConf)
forall a. a -> Maybe Int -> PostgresConnInfo a
PostgresConnInfo Maybe UrlConf
databaseUrl Maybe Int
withEnvRetries
rawConnInfoToUrlConf :: Maybe PostgresConnInfoRaw -> WithEnv (Maybe Common.UrlConf)
rawConnInfoToUrlConf :: Maybe PostgresConnInfoRaw -> WithEnv (Maybe UrlConf)
rawConnInfoToUrlConf Maybe PostgresConnInfoRaw
maybeRawConnInfo = do
[(String, String)]
env <- WithEnvT Identity [(String, String)]
forall r (m :: * -> *). MonadReader r m => m r
ask
let databaseUrlEnvVar :: String
databaseUrlEnvVar = Option () -> String
forall def. Option def -> String
_envVar Option ()
databaseUrlOption
hasDatabaseUrlEnv :: Bool
hasDatabaseUrlEnv = ((String, String) -> Bool) -> [(String, String)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
databaseUrlEnvVar) (String -> Bool)
-> ((String, String) -> String) -> (String, String) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, String) -> String
forall a b. (a, b) -> a
fst) [(String, String)]
env
Maybe UrlConf -> WithEnv (Maybe UrlConf)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe UrlConf -> WithEnv (Maybe UrlConf))
-> Maybe UrlConf -> WithEnv (Maybe UrlConf)
forall a b. (a -> b) -> a -> b
$ case Maybe PostgresConnInfoRaw
maybeRawConnInfo of
Maybe PostgresConnInfoRaw
Nothing ->
if Bool
hasDatabaseUrlEnv
then
UrlConf -> Maybe UrlConf
forall a. a -> Maybe a
Just (UrlConf -> Maybe UrlConf) -> UrlConf -> Maybe UrlConf
forall a b. (a -> b) -> a -> b
$ Text -> UrlConf
Common.UrlFromEnv (Text -> UrlConf) -> Text -> UrlConf
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
databaseUrlEnvVar
else Maybe UrlConf
forall a. Maybe a
Nothing
Just PostgresConnInfoRaw
databaseConn ->
UrlConf -> Maybe UrlConf
forall a. a -> Maybe a
Just (UrlConf -> Maybe UrlConf)
-> (URLTemplate -> UrlConf) -> URLTemplate -> Maybe UrlConf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputWebhook -> UrlConf
Common.UrlValue (InputWebhook -> UrlConf)
-> (URLTemplate -> InputWebhook) -> URLTemplate -> UrlConf
forall b c a. (b -> c) -> (a -> b) -> a -> c
. URLTemplate -> InputWebhook
Common.InputWebhook (URLTemplate -> Maybe UrlConf) -> URLTemplate -> Maybe UrlConf
forall a b. (a -> b) -> a -> b
$ case PostgresConnInfoRaw
databaseConn of
PGConnDatabaseUrl URLTemplate
urlTemplate -> URLTemplate
urlTemplate
PGConnDetails PostgresConnDetailsRaw
connDetails -> PostgresConnDetailsRaw -> URLTemplate
rawConnDetailsToUrl PostgresConnDetailsRaw
connDetails
mkServeOptions :: forall impl. Logging.EnabledLogTypes impl => ServeOptionsRaw impl -> WithEnv (ServeOptions impl)
mkServeOptions :: ServeOptionsRaw impl -> WithEnv (ServeOptions impl)
mkServeOptions ServeOptionsRaw {Bool
Maybe Bool
Maybe Text
Maybe (HashSet (EngineLogType impl))
Maybe (HashSet ExperimentalFeature)
Maybe (HashSet API)
Maybe LogLevel
Maybe InferFunctionPermissions
Maybe DangerouslyCollapseBooleans
Maybe TxIsolation
Maybe CorsConfig
Maybe RoleName
Maybe JWTConfig
Maybe ExtensionsSchema
Maybe PositiveInt
Maybe NonNegativeInt
Maybe (NonNegative Milliseconds)
Maybe (NonNegative Seconds)
Maybe RefetchInterval
Maybe BatchSize
Maybe NamingCase
Maybe AdminSecretHash
Maybe HostPreference
Maybe WSConnectionInitTimeout
Maybe KeepAliveDelay
Maybe OptionalInterval
Maybe Port
RemoteSchemaPermissions
StringifyNumbers
MaintenanceMode ()
MetadataQueryLoggingMode
ConnParamsRaw
AuthHookRaw
rsoExtensionsSchema :: forall impl. ServeOptionsRaw impl -> Maybe ExtensionsSchema
rsoDefaultNamingConvention :: forall impl. ServeOptionsRaw impl -> Maybe NamingCase
rsoEnableMetadataQueryLoggingEnv :: forall impl. ServeOptionsRaw impl -> MetadataQueryLoggingMode
rsoWebSocketConnectionInitTimeout :: forall impl. ServeOptionsRaw impl -> Maybe WSConnectionInitTimeout
rsoGracefulShutdownTimeout :: forall impl. ServeOptionsRaw impl -> Maybe (NonNegative Seconds)
rsoEventsFetchBatchSize :: forall impl. ServeOptionsRaw impl -> Maybe NonNegativeInt
rsoExperimentalFeatures :: forall impl.
ServeOptionsRaw impl -> Maybe (HashSet ExperimentalFeature)
rsoSchemaPollInterval :: forall impl. ServeOptionsRaw impl -> Maybe OptionalInterval
rsoEnableMaintenanceMode :: forall impl. ServeOptionsRaw impl -> MaintenanceMode ()
rsoInferFunctionPermissions :: forall impl. ServeOptionsRaw impl -> Maybe InferFunctionPermissions
rsoWebSocketKeepAlive :: forall impl. ServeOptionsRaw impl -> Maybe KeepAliveDelay
rsoWebSocketCompression :: forall impl. ServeOptionsRaw impl -> Bool
rsoEnableRemoteSchemaPermissions :: forall impl. ServeOptionsRaw impl -> RemoteSchemaPermissions
rsoAsyncActionsFetchInterval :: forall impl. ServeOptionsRaw impl -> Maybe OptionalInterval
rsoEventsFetchInterval :: forall impl.
ServeOptionsRaw impl -> Maybe (NonNegative Milliseconds)
rsoEventsHttpPoolSize :: forall impl. ServeOptionsRaw impl -> Maybe PositiveInt
rsoAdminInternalErrors :: forall impl. ServeOptionsRaw impl -> Maybe Bool
rsoDevMode :: forall impl. ServeOptionsRaw impl -> Bool
rsoLogLevel :: forall impl. ServeOptionsRaw impl -> Maybe LogLevel
rsoEnabledLogTypes :: forall impl.
ServeOptionsRaw impl -> Maybe (HashSet (EngineLogType impl))
rsoEnableAllowlist :: forall impl. ServeOptionsRaw impl -> Bool
rsoStreamingMxBatchSize :: forall impl. ServeOptionsRaw impl -> Maybe BatchSize
rsoStreamingMxRefetchInt :: forall impl. ServeOptionsRaw impl -> Maybe RefetchInterval
rsoMxBatchSize :: forall impl. ServeOptionsRaw impl -> Maybe BatchSize
rsoMxRefetchInt :: forall impl. ServeOptionsRaw impl -> Maybe RefetchInterval
rsoEnabledAPIs :: forall impl. ServeOptionsRaw impl -> Maybe (HashSet API)
rsoDangerousBooleanCollapse :: forall impl.
ServeOptionsRaw impl -> Maybe DangerouslyCollapseBooleans
rsoStringifyNum :: forall impl. ServeOptionsRaw impl -> StringifyNumbers
rsoWsReadCookie :: forall impl. ServeOptionsRaw impl -> Bool
rsoEnableTelemetry :: forall impl. ServeOptionsRaw impl -> Maybe Bool
rsoConsoleAssetsDir :: forall impl. ServeOptionsRaw impl -> Maybe Text
rsoEnableConsole :: forall impl. ServeOptionsRaw impl -> Bool
rsoCorsConfig :: forall impl. ServeOptionsRaw impl -> Maybe CorsConfig
rsoUnAuthRole :: forall impl. ServeOptionsRaw impl -> Maybe RoleName
rsoJwtSecret :: forall impl. ServeOptionsRaw impl -> Maybe JWTConfig
rsoAuthHook :: forall impl. ServeOptionsRaw impl -> AuthHookRaw
rsoAdminSecret :: forall impl. ServeOptionsRaw impl -> Maybe AdminSecretHash
rsoTxIso :: forall impl. ServeOptionsRaw impl -> Maybe TxIsolation
rsoConnParams :: forall impl. ServeOptionsRaw impl -> ConnParamsRaw
rsoHost :: forall impl. ServeOptionsRaw impl -> Maybe HostPreference
rsoPort :: forall impl. ServeOptionsRaw impl -> Maybe Port
rsoExtensionsSchema :: Maybe ExtensionsSchema
rsoDefaultNamingConvention :: Maybe NamingCase
rsoEnableMetadataQueryLoggingEnv :: MetadataQueryLoggingMode
rsoWebSocketConnectionInitTimeout :: Maybe WSConnectionInitTimeout
rsoGracefulShutdownTimeout :: Maybe (NonNegative Seconds)
rsoEventsFetchBatchSize :: Maybe NonNegativeInt
rsoExperimentalFeatures :: Maybe (HashSet ExperimentalFeature)
rsoSchemaPollInterval :: Maybe OptionalInterval
rsoEnableMaintenanceMode :: MaintenanceMode ()
rsoInferFunctionPermissions :: Maybe InferFunctionPermissions
rsoWebSocketKeepAlive :: Maybe KeepAliveDelay
rsoWebSocketCompression :: Bool
rsoEnableRemoteSchemaPermissions :: RemoteSchemaPermissions
rsoAsyncActionsFetchInterval :: Maybe OptionalInterval
rsoEventsFetchInterval :: Maybe (NonNegative Milliseconds)
rsoEventsHttpPoolSize :: Maybe PositiveInt
rsoAdminInternalErrors :: Maybe Bool
rsoDevMode :: Bool
rsoLogLevel :: Maybe LogLevel
rsoEnabledLogTypes :: Maybe (HashSet (EngineLogType impl))
rsoEnableAllowlist :: Bool
rsoStreamingMxBatchSize :: Maybe BatchSize
rsoStreamingMxRefetchInt :: Maybe RefetchInterval
rsoMxBatchSize :: Maybe BatchSize
rsoMxRefetchInt :: Maybe RefetchInterval
rsoEnabledAPIs :: Maybe (HashSet API)
rsoDangerousBooleanCollapse :: Maybe DangerouslyCollapseBooleans
rsoStringifyNum :: StringifyNumbers
rsoWsReadCookie :: Bool
rsoEnableTelemetry :: Maybe Bool
rsoConsoleAssetsDir :: Maybe Text
rsoEnableConsole :: Bool
rsoCorsConfig :: Maybe CorsConfig
rsoUnAuthRole :: Maybe RoleName
rsoJwtSecret :: Maybe JWTConfig
rsoAuthHook :: AuthHookRaw
rsoAdminSecret :: Maybe AdminSecretHash
rsoTxIso :: Maybe TxIsolation
rsoConnParams :: ConnParamsRaw
rsoHost :: Maybe HostPreference
rsoPort :: Maybe Port
..} = do
Port
soPort <- Maybe Port -> Option Port -> WithEnvT Identity Port
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Port
rsoPort Option Port
servePortOption
HostPreference
soHost <- Maybe HostPreference
-> Option HostPreference -> WithEnvT Identity HostPreference
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe HostPreference
rsoHost Option HostPreference
serveHostOption
ConnParams
soConnParams <- ConnParamsRaw -> WithEnvT Identity ConnParams
forall (m :: * -> *).
Monad m =>
ConnParamsRaw -> WithEnvT m ConnParams
mkConnParams ConnParamsRaw
rsoConnParams
TxIsolation
soTxIso <- Maybe TxIsolation
-> Option TxIsolation -> WithEnvT Identity TxIsolation
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe TxIsolation
rsoTxIso Option TxIsolation
txIsolationOption
HashSet AdminSecretHash
soAdminSecret <- HashSet AdminSecretHash
-> (AdminSecretHash -> HashSet AdminSecretHash)
-> Maybe AdminSecretHash
-> HashSet AdminSecretHash
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HashSet AdminSecretHash
forall a. Monoid a => a
mempty (AdminSecretHash -> HashSet AdminSecretHash
forall a. Hashable a => a -> HashSet a
HashSet.singleton) (Maybe AdminSecretHash -> HashSet AdminSecretHash)
-> WithEnvT Identity (Maybe AdminSecretHash)
-> WithEnvT Identity (HashSet AdminSecretHash)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AdminSecretHash
-> [Option ()] -> WithEnvT Identity (Maybe AdminSecretHash)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> [Option ()] -> WithEnvT m (Maybe option)
withOptions Maybe AdminSecretHash
rsoAdminSecret [Option ()
adminSecretOption, Option ()
accessKeyOption]
Maybe AuthHook
soAuthHook <- AuthHookRaw -> WithEnvT Identity (Maybe AuthHook)
forall (m :: * -> *).
Monad m =>
AuthHookRaw -> WithEnvT m (Maybe AuthHook)
mkAuthHook AuthHookRaw
rsoAuthHook
[JWTConfig]
soJwtSecret <- Maybe JWTConfig -> [JWTConfig]
forall a. Maybe a -> [a]
maybeToList (Maybe JWTConfig -> [JWTConfig])
-> WithEnvT Identity (Maybe JWTConfig)
-> WithEnvT Identity [JWTConfig]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe JWTConfig -> Option () -> WithEnvT Identity (Maybe JWTConfig)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe JWTConfig
rsoJwtSecret Option ()
jwtSecretOption
Maybe RoleName
soUnAuthRole <- Maybe RoleName -> Option () -> WithEnvT Identity (Maybe RoleName)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe RoleName
rsoUnAuthRole Option ()
unAuthRoleOption
CorsConfig
soCorsConfig <- Maybe CorsConfig -> WithEnvT Identity CorsConfig
mkCorsConfig Maybe CorsConfig
rsoCorsConfig
Bool
soEnableConsole <- Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *).
Monad m =>
Bool -> Option Bool -> WithEnvT m Bool
withOptionSwitch Bool
rsoEnableConsole Option Bool
enableConsoleOption
Maybe Text
soConsoleAssetsDir <- Maybe Text -> Option () -> WithEnvT Identity (Maybe Text)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe Text
rsoConsoleAssetsDir Option ()
consoleAssetsDirOption
Bool
soEnableTelemetry <- Maybe Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Bool
rsoEnableTelemetry Option Bool
enableTelemetryOption
StringifyNumbers
soStringifyNum <-
case StringifyNumbers
rsoStringifyNum of
StringifyNumbers
Options.Don'tStringifyNumbers -> Maybe StringifyNumbers
-> Option StringifyNumbers -> WithEnvT Identity StringifyNumbers
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe StringifyNumbers
forall a. Maybe a
Nothing Option StringifyNumbers
stringifyNumOption
StringifyNumbers
stringifyNums -> StringifyNumbers -> WithEnvT Identity StringifyNumbers
forall (f :: * -> *) a. Applicative f => a -> f a
pure StringifyNumbers
stringifyNums
DangerouslyCollapseBooleans
soDangerousBooleanCollapse <- Maybe DangerouslyCollapseBooleans
-> Option DangerouslyCollapseBooleans
-> WithEnvT Identity DangerouslyCollapseBooleans
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe DangerouslyCollapseBooleans
rsoDangerousBooleanCollapse Option DangerouslyCollapseBooleans
dangerousBooleanCollapseOption
HashSet API
soEnabledAPIs <- Maybe (HashSet API)
-> Option (HashSet API) -> WithEnvT Identity (HashSet API)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (HashSet API)
rsoEnabledAPIs Option (HashSet API)
enabledAPIsOption
SubscriptionsOptions
soLiveQueryOpts <- do
RefetchInterval
_lqoRefetchInterval <- Maybe RefetchInterval
-> Option RefetchInterval -> WithEnvT Identity RefetchInterval
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe RefetchInterval
rsoMxRefetchInt Option RefetchInterval
mxRefetchDelayOption
BatchSize
_lqoBatchSize <- Maybe BatchSize -> Option BatchSize -> WithEnvT Identity BatchSize
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe BatchSize
rsoMxBatchSize Option BatchSize
mxBatchSizeOption
SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions)
-> SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions
forall a b. (a -> b) -> a -> b
$ SubscriptionsOptions :: BatchSize -> RefetchInterval -> SubscriptionsOptions
Subscription.Options.SubscriptionsOptions {RefetchInterval
BatchSize
_lqoRefetchInterval :: RefetchInterval
_lqoBatchSize :: BatchSize
_lqoBatchSize :: BatchSize
_lqoRefetchInterval :: RefetchInterval
..}
SubscriptionsOptions
soStreamingQueryOpts <- do
RefetchInterval
_lqoRefetchInterval <- Maybe RefetchInterval
-> Option RefetchInterval -> WithEnvT Identity RefetchInterval
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe RefetchInterval
rsoStreamingMxRefetchInt Option RefetchInterval
streamingMxRefetchDelayOption
BatchSize
_lqoBatchSize <- Maybe BatchSize -> Option BatchSize -> WithEnvT Identity BatchSize
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe BatchSize
rsoStreamingMxBatchSize Option BatchSize
streamingMxBatchSizeOption
SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions)
-> SubscriptionsOptions -> WithEnvT Identity SubscriptionsOptions
forall a b. (a -> b) -> a -> b
$ SubscriptionsOptions :: BatchSize -> RefetchInterval -> SubscriptionsOptions
Subscription.Options.SubscriptionsOptions {RefetchInterval
BatchSize
_lqoBatchSize :: BatchSize
_lqoRefetchInterval :: RefetchInterval
_lqoRefetchInterval :: RefetchInterval
_lqoBatchSize :: BatchSize
..}
Bool
soEnableAllowlist <- Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *).
Monad m =>
Bool -> Option Bool -> WithEnvT m Bool
withOptionSwitch Bool
rsoEnableAllowlist Option Bool
enableAllowlistOption
HashSet (EngineLogType impl)
soEnabledLogTypes <- Maybe (HashSet (EngineLogType impl))
-> Option (HashSet (EngineLogType impl))
-> WithEnvT Identity (HashSet (EngineLogType impl))
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (HashSet (EngineLogType impl))
rsoEnabledLogTypes (EnabledLogTypes impl => Option (HashSet (EngineLogType impl))
forall impl.
EnabledLogTypes impl =>
Option (HashSet (EngineLogType impl))
enabledLogsOption @impl)
LogLevel
soLogLevel <- Maybe LogLevel -> Option LogLevel -> WithEnvT Identity LogLevel
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe LogLevel
rsoLogLevel Option LogLevel
logLevelOption
Bool
soDevMode <- Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *).
Monad m =>
Bool -> Option Bool -> WithEnvT m Bool
withOptionSwitch Bool
rsoDevMode Option Bool
graphqlDevModeOption
ResponseInternalErrorsConfig
soResponseInternalErrorsConfig <- Bool -> WithEnvT Identity ResponseInternalErrorsConfig
mkResponseInternalErrorsConfig Bool
soDevMode
PositiveInt
soEventsHttpPoolSize <- Maybe PositiveInt
-> Option PositiveInt -> WithEnvT Identity PositiveInt
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe PositiveInt
rsoEventsHttpPoolSize Option PositiveInt
graphqlEventsHttpPoolSizeOption
NonNegative Milliseconds
soEventsFetchInterval <- Maybe (NonNegative Milliseconds)
-> Option (NonNegative Milliseconds)
-> WithEnvT Identity (NonNegative Milliseconds)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (NonNegative Milliseconds)
rsoEventsFetchInterval Option (NonNegative Milliseconds)
graphqlEventsFetchIntervalOption
OptionalInterval
soAsyncActionsFetchInterval <- Maybe OptionalInterval
-> Option OptionalInterval -> WithEnvT Identity OptionalInterval
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe OptionalInterval
rsoAsyncActionsFetchInterval Option OptionalInterval
asyncActionsFetchIntervalOption
RemoteSchemaPermissions
soEnableRemoteSchemaPermissions <-
case RemoteSchemaPermissions
rsoEnableRemoteSchemaPermissions of
RemoteSchemaPermissions
Options.DisableRemoteSchemaPermissions -> Maybe RemoteSchemaPermissions
-> Option RemoteSchemaPermissions
-> WithEnvT Identity RemoteSchemaPermissions
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe RemoteSchemaPermissions
forall a. Maybe a
Nothing Option RemoteSchemaPermissions
enableRemoteSchemaPermsOption
RemoteSchemaPermissions
enableRemoteSchemaPermissions -> RemoteSchemaPermissions
-> WithEnvT Identity RemoteSchemaPermissions
forall (f :: * -> *) a. Applicative f => a -> f a
pure RemoteSchemaPermissions
enableRemoteSchemaPermissions
ConnectionOptions
soConnectionOptions <- WithEnvT Identity ConnectionOptions
mkConnectionOptions
KeepAliveDelay
soWebSocketKeepAlive <- Maybe KeepAliveDelay
-> Option KeepAliveDelay -> WithEnvT Identity KeepAliveDelay
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe KeepAliveDelay
rsoWebSocketKeepAlive Option KeepAliveDelay
webSocketKeepAliveOption
InferFunctionPermissions
soInferFunctionPermissions <- Maybe InferFunctionPermissions
-> Option InferFunctionPermissions
-> WithEnvT Identity InferFunctionPermissions
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe InferFunctionPermissions
rsoInferFunctionPermissions Option InferFunctionPermissions
inferFunctionPermsOption
MaintenanceMode ()
soEnableMaintenanceMode <- case MaintenanceMode ()
rsoEnableMaintenanceMode of
MaintenanceMode ()
Types.MaintenanceModeDisabled -> Maybe (MaintenanceMode ())
-> Option (MaintenanceMode ())
-> WithEnvT Identity (MaintenanceMode ())
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (MaintenanceMode ())
forall a. Maybe a
Nothing Option (MaintenanceMode ())
enableMaintenanceModeOption
MaintenanceMode ()
maintenanceModeEnabled -> MaintenanceMode () -> WithEnvT Identity (MaintenanceMode ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure MaintenanceMode ()
maintenanceModeEnabled
OptionalInterval
soSchemaPollInterval <- Maybe OptionalInterval
-> Option OptionalInterval -> WithEnvT Identity OptionalInterval
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe OptionalInterval
rsoSchemaPollInterval Option OptionalInterval
schemaPollIntervalOption
HashSet ExperimentalFeature
soExperimentalFeatures <- Maybe (HashSet ExperimentalFeature)
-> Option (HashSet ExperimentalFeature)
-> WithEnvT Identity (HashSet ExperimentalFeature)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (HashSet ExperimentalFeature)
rsoExperimentalFeatures Option (HashSet ExperimentalFeature)
experimentalFeaturesOption
NonNegativeInt
soEventsFetchBatchSize <- Maybe NonNegativeInt
-> Option NonNegativeInt -> WithEnvT Identity NonNegativeInt
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe NonNegativeInt
rsoEventsFetchBatchSize Option NonNegativeInt
eventsFetchBatchSizeOption
NonNegative Seconds
soGracefulShutdownTimeout <- Maybe (NonNegative Seconds)
-> Option (NonNegative Seconds)
-> WithEnvT Identity (NonNegative Seconds)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (NonNegative Seconds)
rsoGracefulShutdownTimeout Option (NonNegative Seconds)
gracefulShutdownOption
WSConnectionInitTimeout
soWebSocketConnectionInitTimeout <- Maybe WSConnectionInitTimeout
-> Option WSConnectionInitTimeout
-> WithEnvT Identity WSConnectionInitTimeout
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe WSConnectionInitTimeout
rsoWebSocketConnectionInitTimeout Option WSConnectionInitTimeout
webSocketConnectionInitTimeoutOption
let soEventingMode :: EventingMode
soEventingMode = EventingMode
Types.EventingEnabled
let soReadOnlyMode :: ReadOnlyMode
soReadOnlyMode = ReadOnlyMode
Types.ReadOnlyModeDisabled
MetadataQueryLoggingMode
soEnableMetadataQueryLogging <- case MetadataQueryLoggingMode
rsoEnableMetadataQueryLoggingEnv of
MetadataQueryLoggingMode
Server.Logging.MetadataQueryLoggingDisabled -> Maybe MetadataQueryLoggingMode
-> Option MetadataQueryLoggingMode
-> WithEnvT Identity MetadataQueryLoggingMode
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe MetadataQueryLoggingMode
forall a. Maybe a
Nothing Option MetadataQueryLoggingMode
enableMetadataQueryLoggingOption
MetadataQueryLoggingMode
metadataQueryLoggingEnabled -> MetadataQueryLoggingMode
-> WithEnvT Identity MetadataQueryLoggingMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure MetadataQueryLoggingMode
metadataQueryLoggingEnabled
Maybe NamingCase
soDefaultNamingConvention <- Maybe NamingCase
-> Option () -> WithEnvT Identity (Maybe NamingCase)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe NamingCase
rsoDefaultNamingConvention Option ()
defaultNamingConventionOption
ExtensionsSchema
soExtensionsSchema <- Maybe ExtensionsSchema
-> Option ExtensionsSchema -> WithEnvT Identity ExtensionsSchema
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe ExtensionsSchema
rsoExtensionsSchema Option ExtensionsSchema
metadataDBExtensionsSchemaOption
ServeOptions impl -> WithEnv (ServeOptions impl)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ServeOptions :: forall impl.
Port
-> HostPreference
-> ConnParams
-> TxIsolation
-> HashSet AdminSecretHash
-> Maybe AuthHook
-> [JWTConfig]
-> Maybe RoleName
-> CorsConfig
-> Bool
-> Maybe Text
-> Bool
-> StringifyNumbers
-> DangerouslyCollapseBooleans
-> HashSet API
-> SubscriptionsOptions
-> SubscriptionsOptions
-> Bool
-> HashSet (EngineLogType impl)
-> LogLevel
-> ResponseInternalErrorsConfig
-> PositiveInt
-> NonNegative Milliseconds
-> OptionalInterval
-> RemoteSchemaPermissions
-> ConnectionOptions
-> KeepAliveDelay
-> InferFunctionPermissions
-> MaintenanceMode ()
-> OptionalInterval
-> HashSet ExperimentalFeature
-> NonNegativeInt
-> Bool
-> NonNegative Seconds
-> WSConnectionInitTimeout
-> EventingMode
-> ReadOnlyMode
-> MetadataQueryLoggingMode
-> Maybe NamingCase
-> ExtensionsSchema
-> ServeOptions impl
ServeOptions {Bool
[JWTConfig]
Maybe Text
Maybe RoleName
Maybe NamingCase
Maybe AuthHook
HashSet (EngineLogType impl)
HashSet ExperimentalFeature
HashSet AdminSecretHash
HashSet API
LogLevel
RemoteSchemaPermissions
InferFunctionPermissions
DangerouslyCollapseBooleans
StringifyNumbers
ConnParams
TxIsolation
CorsConfig
ExtensionsSchema
PositiveInt
NonNegativeInt
NonNegative Milliseconds
NonNegative Seconds
SubscriptionsOptions
EventingMode
ReadOnlyMode
MaintenanceMode ()
MetadataQueryLoggingMode
HostPreference
ConnectionOptions
ResponseInternalErrorsConfig
WSConnectionInitTimeout
KeepAliveDelay
OptionalInterval
Port
soExtensionsSchema :: ExtensionsSchema
soDefaultNamingConvention :: Maybe NamingCase
soEnableMetadataQueryLogging :: MetadataQueryLoggingMode
soReadOnlyMode :: ReadOnlyMode
soEventingMode :: EventingMode
soWebSocketConnectionInitTimeout :: WSConnectionInitTimeout
soGracefulShutdownTimeout :: NonNegative Seconds
soDevMode :: Bool
soEventsFetchBatchSize :: NonNegativeInt
soExperimentalFeatures :: HashSet ExperimentalFeature
soSchemaPollInterval :: OptionalInterval
soEnableMaintenanceMode :: MaintenanceMode ()
soInferFunctionPermissions :: InferFunctionPermissions
soWebSocketKeepAlive :: KeepAliveDelay
soConnectionOptions :: ConnectionOptions
soEnableRemoteSchemaPermissions :: RemoteSchemaPermissions
soAsyncActionsFetchInterval :: OptionalInterval
soEventsFetchInterval :: NonNegative Milliseconds
soEventsHttpPoolSize :: PositiveInt
soResponseInternalErrorsConfig :: ResponseInternalErrorsConfig
soLogLevel :: LogLevel
soEnabledLogTypes :: HashSet (EngineLogType impl)
soEnableAllowlist :: Bool
soStreamingQueryOpts :: SubscriptionsOptions
soLiveQueryOpts :: SubscriptionsOptions
soEnabledAPIs :: HashSet API
soDangerousBooleanCollapse :: DangerouslyCollapseBooleans
soStringifyNum :: StringifyNumbers
soEnableTelemetry :: Bool
soConsoleAssetsDir :: Maybe Text
soEnableConsole :: Bool
soCorsConfig :: CorsConfig
soUnAuthRole :: Maybe RoleName
soJwtSecret :: [JWTConfig]
soAuthHook :: Maybe AuthHook
soAdminSecret :: HashSet AdminSecretHash
soTxIso :: TxIsolation
soConnParams :: ConnParams
soHost :: HostPreference
soPort :: Port
soExtensionsSchema :: ExtensionsSchema
soDefaultNamingConvention :: Maybe NamingCase
soEnableMetadataQueryLogging :: MetadataQueryLoggingMode
soReadOnlyMode :: ReadOnlyMode
soEventingMode :: EventingMode
soWebSocketConnectionInitTimeout :: WSConnectionInitTimeout
soGracefulShutdownTimeout :: NonNegative Seconds
soEventsFetchBatchSize :: NonNegativeInt
soExperimentalFeatures :: HashSet ExperimentalFeature
soSchemaPollInterval :: OptionalInterval
soEnableMaintenanceMode :: MaintenanceMode ()
soInferFunctionPermissions :: InferFunctionPermissions
soWebSocketKeepAlive :: KeepAliveDelay
soConnectionOptions :: ConnectionOptions
soEnableRemoteSchemaPermissions :: RemoteSchemaPermissions
soAsyncActionsFetchInterval :: OptionalInterval
soEventsFetchInterval :: NonNegative Milliseconds
soEventsHttpPoolSize :: PositiveInt
soResponseInternalErrorsConfig :: ResponseInternalErrorsConfig
soDevMode :: Bool
soLogLevel :: LogLevel
soEnabledLogTypes :: HashSet (EngineLogType impl)
soEnableAllowlist :: Bool
soStreamingQueryOpts :: SubscriptionsOptions
soLiveQueryOpts :: SubscriptionsOptions
soEnabledAPIs :: HashSet API
soDangerousBooleanCollapse :: DangerouslyCollapseBooleans
soStringifyNum :: StringifyNumbers
soEnableTelemetry :: Bool
soConsoleAssetsDir :: Maybe Text
soEnableConsole :: Bool
soCorsConfig :: CorsConfig
soUnAuthRole :: Maybe RoleName
soJwtSecret :: [JWTConfig]
soAuthHook :: Maybe AuthHook
soAdminSecret :: HashSet AdminSecretHash
soTxIso :: TxIsolation
soConnParams :: ConnParams
soHost :: HostPreference
soPort :: Port
..}
where
mkConnParams :: ConnParamsRaw -> WithEnvT m ConnParams
mkConnParams ConnParamsRaw {Maybe Bool
Maybe NonNegativeInt
Maybe (NonNegative NominalDiffTime)
rcpPoolTimeout :: ConnParamsRaw -> Maybe (NonNegative NominalDiffTime)
rcpAllowPrepare :: ConnParamsRaw -> Maybe Bool
rcpConnLifetime :: ConnParamsRaw -> Maybe (NonNegative NominalDiffTime)
rcpIdleTime :: ConnParamsRaw -> Maybe NonNegativeInt
rcpConns :: ConnParamsRaw -> Maybe NonNegativeInt
rcpStripes :: ConnParamsRaw -> Maybe NonNegativeInt
rcpPoolTimeout :: Maybe (NonNegative NominalDiffTime)
rcpAllowPrepare :: Maybe Bool
rcpConnLifetime :: Maybe (NonNegative NominalDiffTime)
rcpIdleTime :: Maybe NonNegativeInt
rcpConns :: Maybe NonNegativeInt
rcpStripes :: Maybe NonNegativeInt
..} = do
Int
cpStripes <- NonNegativeInt -> Int
Numeric.getNonNegativeInt (NonNegativeInt -> Int)
-> WithEnvT m NonNegativeInt -> WithEnvT m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NonNegativeInt
-> Option NonNegativeInt -> WithEnvT m NonNegativeInt
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe NonNegativeInt
rcpStripes Option NonNegativeInt
pgStripesOption
Int
cpConns <- NonNegativeInt -> Int
Numeric.getNonNegativeInt (NonNegativeInt -> Int)
-> WithEnvT m NonNegativeInt -> WithEnvT m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NonNegativeInt
-> Option NonNegativeInt -> WithEnvT m NonNegativeInt
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe NonNegativeInt
rcpConns Option NonNegativeInt
pgConnsOption
Int
cpIdleTime <- NonNegativeInt -> Int
Numeric.getNonNegativeInt (NonNegativeInt -> Int)
-> WithEnvT m NonNegativeInt -> WithEnvT m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe NonNegativeInt
-> Option NonNegativeInt -> WithEnvT m NonNegativeInt
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe NonNegativeInt
rcpIdleTime Option NonNegativeInt
pgTimeoutOption
Bool
cpAllowPrepare <- Maybe Bool -> Option Bool -> WithEnvT m Bool
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Bool
rcpAllowPrepare Option Bool
pgUsePreparedStatementsOption
Maybe NominalDiffTime
cpMbLifetime <- do
NominalDiffTime
lifetime <- NonNegative NominalDiffTime -> NominalDiffTime
forall a. NonNegative a -> a
Numeric.getNonNegative (NonNegative NominalDiffTime -> NominalDiffTime)
-> WithEnvT m (NonNegative NominalDiffTime)
-> WithEnvT m NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonNegative NominalDiffTime)
-> Option (NonNegative NominalDiffTime)
-> WithEnvT m (NonNegative NominalDiffTime)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe (NonNegative NominalDiffTime)
rcpConnLifetime Option (NonNegative NominalDiffTime)
pgConnLifetimeOption
if NominalDiffTime
lifetime NominalDiffTime -> NominalDiffTime -> Bool
forall a. Eq a => a -> a -> Bool
== NominalDiffTime
0
then Maybe NominalDiffTime -> WithEnvT m (Maybe NominalDiffTime)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe NominalDiffTime
forall a. Maybe a
Nothing
else Maybe NominalDiffTime -> WithEnvT m (Maybe NominalDiffTime)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NominalDiffTime -> Maybe NominalDiffTime
forall a. a -> Maybe a
Just NominalDiffTime
lifetime)
Maybe NominalDiffTime
cpTimeout <- (NonNegative NominalDiffTime -> NominalDiffTime)
-> Maybe (NonNegative NominalDiffTime) -> Maybe NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NonNegative NominalDiffTime -> NominalDiffTime
forall a. NonNegative a -> a
Numeric.getNonNegative (Maybe (NonNegative NominalDiffTime) -> Maybe NominalDiffTime)
-> WithEnvT m (Maybe (NonNegative NominalDiffTime))
-> WithEnvT m (Maybe NominalDiffTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (NonNegative NominalDiffTime)
-> Option () -> WithEnvT m (Maybe (NonNegative NominalDiffTime))
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe (NonNegative NominalDiffTime)
rcpPoolTimeout Option ()
pgPoolTimeoutOption
let cpCancel :: Bool
cpCancel = Bool
True
ConnParams -> WithEnvT m ConnParams
forall (m :: * -> *) a. Monad m => a -> m a
return (ConnParams -> WithEnvT m ConnParams)
-> ConnParams -> WithEnvT m ConnParams
forall a b. (a -> b) -> a -> b
$
ConnParams :: Int
-> Int
-> Int
-> Bool
-> Maybe NominalDiffTime
-> Maybe NominalDiffTime
-> Bool
-> ConnParams
Query.ConnParams {Bool
Int
Maybe NominalDiffTime
cpTimeout :: Maybe NominalDiffTime
cpStripes :: Int
cpMbLifetime :: Maybe NominalDiffTime
cpIdleTime :: Int
cpConns :: Int
cpCancel :: Bool
cpAllowPrepare :: Bool
cpCancel :: Bool
cpTimeout :: Maybe NominalDiffTime
cpMbLifetime :: Maybe NominalDiffTime
cpAllowPrepare :: Bool
cpIdleTime :: Int
cpConns :: Int
cpStripes :: Int
..}
mkAuthHook :: AuthHookRaw -> WithEnvT m (Maybe AuthHook)
mkAuthHook (AuthHookRaw Maybe Text
mUrl Maybe AuthHookType
mType) = do
Maybe Text
mUrlEnv <- Maybe Text -> Option () -> WithEnvT m (Maybe Text)
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option () -> WithEnvT m (Maybe option)
withOption Maybe Text
mUrl Option ()
authHookOption
AuthHookType
authMode <-
Maybe AuthHookType
-> WithEnvT m AuthHookType -> WithEnvT m AuthHookType
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
onNothing
Maybe AuthHookType
mType
( AuthHookType -> Maybe AuthHookType -> AuthHookType
forall a. a -> Maybe a -> a
fromMaybe (Option AuthHookType -> AuthHookType
forall def. Option def -> def
_default Option AuthHookType
authHookModeOption)
(Maybe AuthHookType -> AuthHookType)
-> WithEnvT m (Maybe AuthHookType) -> WithEnvT m AuthHookType
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [String] -> WithEnvT m (Maybe AuthHookType)
forall (m :: * -> *) a.
(Monad m, FromEnv a) =>
[String] -> WithEnvT m (Maybe a)
considerEnvs
[Option AuthHookType -> String
forall def. Option def -> String
_envVar Option AuthHookType
authHookModeOption, String
"HASURA_GRAPHQL_AUTH_HOOK_TYPE"]
)
Maybe AuthHook -> WithEnvT m (Maybe AuthHook)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe AuthHook -> WithEnvT m (Maybe AuthHook))
-> Maybe AuthHook -> WithEnvT m (Maybe AuthHook)
forall a b. (a -> b) -> a -> b
$ (Text -> AuthHookType -> AuthHook
`Auth.AuthHook` AuthHookType
authMode) (Text -> AuthHook) -> Maybe Text -> Maybe AuthHook
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
mUrlEnv
mkCorsConfig :: Maybe CorsConfig -> WithEnvT Identity CorsConfig
mkCorsConfig Maybe CorsConfig
mCfg = do
CorsConfig
corsCfg <- do
Bool
corsDisabled <- Maybe Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Bool
forall a. Maybe a
Nothing Option Bool
disableCorsOption
if Bool
corsDisabled
then CorsConfig -> WithEnvT Identity CorsConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> CorsConfig
Cors.CCDisabled (Bool -> CorsConfig) -> Bool -> CorsConfig
forall a b. (a -> b) -> a -> b
$ Option Bool -> Bool
forall def. Option def -> def
_default Option Bool
disableCorsOption)
else Maybe CorsConfig
-> Option CorsConfig -> WithEnvT Identity CorsConfig
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe CorsConfig
mCfg Option CorsConfig
corsDomainOption
Bool
readCookVal <-
case Bool
rsoWsReadCookie of
Bool
False -> Maybe Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Bool
forall a. Maybe a
Nothing Option Bool
wsReadCookieOption
Bool
p -> Bool -> WithEnvT Identity Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
p
Bool
wsReadCookie <- case (CorsConfig -> Bool
Cors.isCorsDisabled CorsConfig
corsCfg, Bool
readCookVal) of
(Bool
True, Bool
_) -> Bool -> WithEnvT Identity Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
readCookVal
(Bool
False, Bool
True) ->
String -> WithEnvT Identity Bool
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (String -> WithEnvT Identity Bool)
-> String -> WithEnvT Identity Bool
forall a b. (a -> b) -> a -> b
$
Option Bool -> String
forall def. Option def -> String
_envVar Option Bool
wsReadCookieOption
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" can only be used when CORS is disabled"
(Bool
False, Bool
False) -> Bool -> WithEnvT Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
CorsConfig -> WithEnvT Identity CorsConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CorsConfig -> WithEnvT Identity CorsConfig)
-> CorsConfig -> WithEnvT Identity CorsConfig
forall a b. (a -> b) -> a -> b
$ case CorsConfig
corsCfg of
Cors.CCDisabled Bool
_ -> Bool -> CorsConfig
Cors.CCDisabled Bool
wsReadCookie
CorsConfig
_ -> CorsConfig
corsCfg
mkResponseInternalErrorsConfig :: Bool -> WithEnvT Identity ResponseInternalErrorsConfig
mkResponseInternalErrorsConfig Bool
devMode = do
Bool
adminInternalErrors <- Maybe Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *) option.
(Monad m, FromEnv option) =>
Maybe option -> Option option -> WithEnvT m option
withOptionDefault Maybe Bool
rsoAdminInternalErrors Option Bool
graphqlAdminInternalErrorsOption
if
| Bool
devMode -> ResponseInternalErrorsConfig
-> WithEnvT Identity ResponseInternalErrorsConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure ResponseInternalErrorsConfig
InternalErrorsAllRequests
| Bool
adminInternalErrors -> ResponseInternalErrorsConfig
-> WithEnvT Identity ResponseInternalErrorsConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure ResponseInternalErrorsConfig
InternalErrorsAdminOnly
| Bool
otherwise -> ResponseInternalErrorsConfig
-> WithEnvT Identity ResponseInternalErrorsConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure ResponseInternalErrorsConfig
InternalErrorsDisabled
mkConnectionOptions :: WithEnvT Identity ConnectionOptions
mkConnectionOptions = do
Bool
webSocketCompressionFromEnv <- Bool -> Option Bool -> WithEnvT Identity Bool
forall (m :: * -> *).
Monad m =>
Bool -> Option Bool -> WithEnvT m Bool
withOptionSwitch Bool
rsoWebSocketCompression Option Bool
webSocketCompressionOption
ConnectionOptions -> WithEnvT Identity ConnectionOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ConnectionOptions -> WithEnvT Identity ConnectionOptions)
-> ConnectionOptions -> WithEnvT Identity ConnectionOptions
forall a b. (a -> b) -> a -> b
$
ConnectionOptions
WebSockets.defaultConnectionOptions
{ connectionCompressionOptions :: CompressionOptions
WebSockets.connectionCompressionOptions =
if Bool
webSocketCompressionFromEnv
then PermessageDeflate -> CompressionOptions
WebSockets.PermessageDeflateCompression PermessageDeflate
WebSockets.defaultPermessageDeflate
else CompressionOptions
WebSockets.NoCompression
}