{-# LANGUAGE ViewPatterns #-}
module Hasura.Server.Init.Config
(
Option (..),
optionPP,
HGEOptionsRaw (..),
horDatabaseUrl,
horMetadataDbUrl,
horCommand,
HGEOptions (..),
hoCommand,
PostgresConnInfo (..),
pciDatabaseConn,
pciRetries,
PostgresConnInfoRaw (..),
_PGConnDatabaseUrl,
_PGConnDetails,
mkUrlConnInfo,
PostgresConnDetailsRaw (..),
HGECommand (..),
_HCServe,
ServeOptionsRaw (..),
ConsoleStatus (..),
isConsoleEnabled,
AdminInternalErrorsStatus (..),
isAdminInternalErrorsEnabled,
isWebSocketCompressionEnabled,
AllowListStatus (..),
isAllowListEnabled,
DevModeStatus (..),
isDevModeEnabled,
TelemetryStatus (..),
isTelemetryEnabled,
WsReadCookieStatus (..),
isWsReadCookieEnabled,
Port,
_getPort,
mkPort,
unsafePort,
API (..),
KeepAliveDelay (..),
OptionalInterval (..),
AuthHookRaw (..),
ConnParamsRaw (..),
ResponseInternalErrorsConfig (..),
WSConnectionInitTimeout (..),
msToOptionalInterval,
rawConnDetailsToUrl,
rawConnDetailsToUrlText,
shouldIncludeInternal,
ServeOptions (..),
DowngradeOptions (..),
)
where
import Control.Lens (Lens', Prism')
import Control.Lens qualified as Lens
import Data.Aeson (FromJSON, ToJSON, (.:), (.:?), (.=))
import Data.Aeson qualified as J
import Data.Scientific qualified as Scientific
import Data.Text qualified as Text
import Data.Time qualified as Time
import Data.URL.Template qualified as Template
import Database.PG.Query qualified as Query
import Hasura.Backends.Postgres.Connection.MonadTx qualified as MonadTx
import Hasura.GraphQL.Execute.Subscription.Options qualified as Subscription.Options
import Hasura.Logging qualified as Logging
import Hasura.Prelude
import Hasura.RQL.Types.Common qualified as Common
import Hasura.RQL.Types.Metadata (MetadataDefaults)
import Hasura.RQL.Types.NamingCase (NamingCase)
import Hasura.RQL.Types.Roles (RoleName, adminRoleName)
import Hasura.RQL.Types.Schema.Options qualified as Schema.Options
import Hasura.Server.Auth qualified as Auth
import Hasura.Server.Cors qualified as Cors
import Hasura.Server.Logging qualified as Server.Logging
import Hasura.Server.Types qualified as Server.Types
import Network.Wai.Handler.Warp qualified as Warp
import Network.WebSockets qualified as WebSockets
import Refined (NonNegative, Positive, Refined, unrefine)
data Option def = Option
{ forall def. Option def -> def
_default :: def,
forall def. Option def -> String
_envVar :: String,
forall def. Option def -> String
_helpMessage :: String
}
deriving ((forall a b. (a -> b) -> Option a -> Option b)
-> (forall a b. a -> Option b -> Option a) -> Functor Option
forall a b. a -> Option b -> Option a
forall a b. (a -> b) -> Option a -> Option b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Option a -> Option b
fmap :: forall a b. (a -> b) -> Option a -> Option b
$c<$ :: forall a b. a -> Option b -> Option a
<$ :: forall a b. a -> Option b -> Option a
Functor)
optionPP :: Option a -> (String, String)
optionPP :: forall a. Option a -> (String, String)
optionPP = Option a -> String
forall def. Option def -> String
_envVar (Option a -> String)
-> (Option a -> String) -> Option a -> (String, String)
forall b c c'. (b -> c) -> (b -> c') -> b -> (c, c')
forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& Option a -> String
forall def. Option def -> String
_helpMessage
data HGEOptionsRaw impl = HGEOptionsRaw
{ forall impl.
HGEOptionsRaw impl -> PostgresConnInfo (Maybe PostgresConnInfoRaw)
_horDatabaseUrl :: PostgresConnInfo (Maybe PostgresConnInfoRaw),
forall impl. HGEOptionsRaw impl -> Maybe String
_horMetadataDbUrl :: Maybe String,
forall impl. HGEOptionsRaw impl -> HGECommand impl
_horCommand :: HGECommand impl
}
horDatabaseUrl :: Lens' (HGEOptionsRaw impl) (PostgresConnInfo (Maybe PostgresConnInfoRaw))
horDatabaseUrl :: forall impl (f :: * -> *).
Functor f =>
(PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> f (PostgresConnInfo (Maybe PostgresConnInfoRaw)))
-> HGEOptionsRaw impl -> f (HGEOptionsRaw impl)
horDatabaseUrl = (HGEOptionsRaw impl
-> PostgresConnInfo (Maybe PostgresConnInfoRaw))
-> (HGEOptionsRaw impl
-> PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(PostgresConnInfo (Maybe PostgresConnInfoRaw))
(PostgresConnInfo (Maybe PostgresConnInfoRaw))
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens HGEOptionsRaw impl -> PostgresConnInfo (Maybe PostgresConnInfoRaw)
forall impl.
HGEOptionsRaw impl -> PostgresConnInfo (Maybe PostgresConnInfoRaw)
_horDatabaseUrl ((HGEOptionsRaw impl
-> PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(PostgresConnInfo (Maybe PostgresConnInfoRaw))
(PostgresConnInfo (Maybe PostgresConnInfoRaw)))
-> (HGEOptionsRaw impl
-> PostgresConnInfo (Maybe PostgresConnInfoRaw)
-> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(PostgresConnInfo (Maybe PostgresConnInfoRaw))
(PostgresConnInfo (Maybe PostgresConnInfoRaw))
forall a b. (a -> b) -> a -> b
$ \HGEOptionsRaw impl
hdu PostgresConnInfo (Maybe PostgresConnInfoRaw)
a -> HGEOptionsRaw impl
hdu {_horDatabaseUrl :: PostgresConnInfo (Maybe PostgresConnInfoRaw)
_horDatabaseUrl = PostgresConnInfo (Maybe PostgresConnInfoRaw)
a}
horMetadataDbUrl :: Lens' (HGEOptionsRaw impl) (Maybe String)
horMetadataDbUrl :: forall impl (f :: * -> *).
Functor f =>
(Maybe String -> f (Maybe String))
-> HGEOptionsRaw impl -> f (HGEOptionsRaw impl)
horMetadataDbUrl = (HGEOptionsRaw impl -> Maybe String)
-> (HGEOptionsRaw impl -> Maybe String -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(Maybe String)
(Maybe String)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens HGEOptionsRaw impl -> Maybe String
forall impl. HGEOptionsRaw impl -> Maybe String
_horMetadataDbUrl ((HGEOptionsRaw impl -> Maybe String -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(Maybe String)
(Maybe String))
-> (HGEOptionsRaw impl -> Maybe String -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(Maybe String)
(Maybe String)
forall a b. (a -> b) -> a -> b
$ \HGEOptionsRaw impl
hdu Maybe String
a -> HGEOptionsRaw impl
hdu {_horMetadataDbUrl :: Maybe String
_horMetadataDbUrl = Maybe String
a}
horCommand :: Lens' (HGEOptionsRaw impl) (HGECommand impl)
horCommand :: forall impl (f :: * -> *).
Functor f =>
(HGECommand impl -> f (HGECommand impl))
-> HGEOptionsRaw impl -> f (HGEOptionsRaw impl)
horCommand = (HGEOptionsRaw impl -> HGECommand impl)
-> (HGEOptionsRaw impl -> HGECommand impl -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(HGECommand impl)
(HGECommand impl)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens HGEOptionsRaw impl -> HGECommand impl
forall impl. HGEOptionsRaw impl -> HGECommand impl
_horCommand ((HGEOptionsRaw impl -> HGECommand impl -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(HGECommand impl)
(HGECommand impl))
-> (HGEOptionsRaw impl -> HGECommand impl -> HGEOptionsRaw impl)
-> Lens
(HGEOptionsRaw impl)
(HGEOptionsRaw impl)
(HGECommand impl)
(HGECommand impl)
forall a b. (a -> b) -> a -> b
$ \HGEOptionsRaw impl
hdu HGECommand impl
a -> HGEOptionsRaw impl
hdu {_horCommand :: HGECommand impl
_horCommand = HGECommand impl
a}
data HGEOptions impl = HGEOptions
{ forall impl. HGEOptions impl -> PostgresConnInfo (Maybe UrlConf)
_hoDatabaseUrl :: PostgresConnInfo (Maybe Common.UrlConf),
forall impl. HGEOptions impl -> Maybe String
_hoMetadataDbUrl :: Maybe String,
forall impl. HGEOptions impl -> HGECommand impl
_hoCommand :: HGECommand impl
}
hoCommand :: Lens' (HGEOptions impl) (HGECommand impl)
hoCommand :: forall impl (f :: * -> *).
Functor f =>
(HGECommand impl -> f (HGECommand impl))
-> HGEOptions impl -> f (HGEOptions impl)
hoCommand = (HGEOptions impl -> HGECommand impl)
-> (HGEOptions impl -> HGECommand impl -> HGEOptions impl)
-> Lens
(HGEOptions impl)
(HGEOptions impl)
(HGECommand impl)
(HGECommand impl)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens HGEOptions impl -> HGECommand impl
forall impl. HGEOptions impl -> HGECommand impl
_hoCommand ((HGEOptions impl -> HGECommand impl -> HGEOptions impl)
-> Lens
(HGEOptions impl)
(HGEOptions impl)
(HGECommand impl)
(HGECommand impl))
-> (HGEOptions impl -> HGECommand impl -> HGEOptions impl)
-> Lens
(HGEOptions impl)
(HGEOptions impl)
(HGECommand impl)
(HGECommand impl)
forall a b. (a -> b) -> a -> b
$ \HGEOptions impl
hdu HGECommand impl
a -> HGEOptions impl
hdu {_hoCommand :: HGECommand impl
_hoCommand = HGECommand impl
a}
data PostgresConnInfo a = PostgresConnInfo
{ forall a. PostgresConnInfo a -> a
_pciDatabaseConn :: a,
forall a. PostgresConnInfo a -> Maybe Int
_pciRetries :: Maybe Int
}
deriving (Int -> PostgresConnInfo a -> ShowS
[PostgresConnInfo a] -> ShowS
PostgresConnInfo a -> String
(Int -> PostgresConnInfo a -> ShowS)
-> (PostgresConnInfo a -> String)
-> ([PostgresConnInfo a] -> ShowS)
-> Show (PostgresConnInfo a)
forall a. Show a => Int -> PostgresConnInfo a -> ShowS
forall a. Show a => [PostgresConnInfo a] -> ShowS
forall a. Show a => PostgresConnInfo a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> PostgresConnInfo a -> ShowS
showsPrec :: Int -> PostgresConnInfo a -> ShowS
$cshow :: forall a. Show a => PostgresConnInfo a -> String
show :: PostgresConnInfo a -> String
$cshowList :: forall a. Show a => [PostgresConnInfo a] -> ShowS
showList :: [PostgresConnInfo a] -> ShowS
Show, PostgresConnInfo a -> PostgresConnInfo a -> Bool
(PostgresConnInfo a -> PostgresConnInfo a -> Bool)
-> (PostgresConnInfo a -> PostgresConnInfo a -> Bool)
-> Eq (PostgresConnInfo a)
forall a. Eq a => PostgresConnInfo a -> PostgresConnInfo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => PostgresConnInfo a -> PostgresConnInfo a -> Bool
== :: PostgresConnInfo a -> PostgresConnInfo a -> Bool
$c/= :: forall a. Eq a => PostgresConnInfo a -> PostgresConnInfo a -> Bool
/= :: PostgresConnInfo a -> PostgresConnInfo a -> Bool
Eq, (forall a b. (a -> b) -> PostgresConnInfo a -> PostgresConnInfo b)
-> (forall a b. a -> PostgresConnInfo b -> PostgresConnInfo a)
-> Functor PostgresConnInfo
forall a b. a -> PostgresConnInfo b -> PostgresConnInfo a
forall a b. (a -> b) -> PostgresConnInfo a -> PostgresConnInfo b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> PostgresConnInfo a -> PostgresConnInfo b
fmap :: forall a b. (a -> b) -> PostgresConnInfo a -> PostgresConnInfo b
$c<$ :: forall a b. a -> PostgresConnInfo b -> PostgresConnInfo a
<$ :: forall a b. a -> PostgresConnInfo b -> PostgresConnInfo a
Functor, (forall m. Monoid m => PostgresConnInfo m -> m)
-> (forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m)
-> (forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m)
-> (forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b)
-> (forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b)
-> (forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b)
-> (forall a. (a -> a -> a) -> PostgresConnInfo a -> a)
-> (forall a. (a -> a -> a) -> PostgresConnInfo a -> a)
-> (forall a. PostgresConnInfo a -> [a])
-> (forall a. PostgresConnInfo a -> Bool)
-> (forall a. PostgresConnInfo a -> Int)
-> (forall a. Eq a => a -> PostgresConnInfo a -> Bool)
-> (forall a. Ord a => PostgresConnInfo a -> a)
-> (forall a. Ord a => PostgresConnInfo a -> a)
-> (forall a. Num a => PostgresConnInfo a -> a)
-> (forall a. Num a => PostgresConnInfo a -> a)
-> Foldable PostgresConnInfo
forall a. Eq a => a -> PostgresConnInfo a -> Bool
forall a. Num a => PostgresConnInfo a -> a
forall a. Ord a => PostgresConnInfo a -> a
forall m. Monoid m => PostgresConnInfo m -> m
forall a. PostgresConnInfo a -> Bool
forall a. PostgresConnInfo a -> Int
forall a. PostgresConnInfo a -> [a]
forall a. (a -> a -> a) -> PostgresConnInfo a -> a
forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m
forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b
forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => PostgresConnInfo m -> m
fold :: forall m. Monoid m => PostgresConnInfo m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> PostgresConnInfo a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b
foldr :: forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> PostgresConnInfo a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b
foldl :: forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> PostgresConnInfo a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> PostgresConnInfo a -> a
foldr1 :: forall a. (a -> a -> a) -> PostgresConnInfo a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> PostgresConnInfo a -> a
foldl1 :: forall a. (a -> a -> a) -> PostgresConnInfo a -> a
$ctoList :: forall a. PostgresConnInfo a -> [a]
toList :: forall a. PostgresConnInfo a -> [a]
$cnull :: forall a. PostgresConnInfo a -> Bool
null :: forall a. PostgresConnInfo a -> Bool
$clength :: forall a. PostgresConnInfo a -> Int
length :: forall a. PostgresConnInfo a -> Int
$celem :: forall a. Eq a => a -> PostgresConnInfo a -> Bool
elem :: forall a. Eq a => a -> PostgresConnInfo a -> Bool
$cmaximum :: forall a. Ord a => PostgresConnInfo a -> a
maximum :: forall a. Ord a => PostgresConnInfo a -> a
$cminimum :: forall a. Ord a => PostgresConnInfo a -> a
minimum :: forall a. Ord a => PostgresConnInfo a -> a
$csum :: forall a. Num a => PostgresConnInfo a -> a
sum :: forall a. Num a => PostgresConnInfo a -> a
$cproduct :: forall a. Num a => PostgresConnInfo a -> a
product :: forall a. Num a => PostgresConnInfo a -> a
Foldable, Functor PostgresConnInfo
Foldable PostgresConnInfo
Functor PostgresConnInfo
-> Foldable PostgresConnInfo
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PostgresConnInfo a -> f (PostgresConnInfo b))
-> (forall (f :: * -> *) a.
Applicative f =>
PostgresConnInfo (f a) -> f (PostgresConnInfo a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PostgresConnInfo a -> m (PostgresConnInfo b))
-> (forall (m :: * -> *) a.
Monad m =>
PostgresConnInfo (m a) -> m (PostgresConnInfo a))
-> Traversable PostgresConnInfo
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
PostgresConnInfo (m a) -> m (PostgresConnInfo a)
forall (f :: * -> *) a.
Applicative f =>
PostgresConnInfo (f a) -> f (PostgresConnInfo a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PostgresConnInfo a -> m (PostgresConnInfo b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PostgresConnInfo a -> f (PostgresConnInfo b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PostgresConnInfo a -> f (PostgresConnInfo b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> PostgresConnInfo a -> f (PostgresConnInfo b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
PostgresConnInfo (f a) -> f (PostgresConnInfo a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
PostgresConnInfo (f a) -> f (PostgresConnInfo a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PostgresConnInfo a -> m (PostgresConnInfo b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> PostgresConnInfo a -> m (PostgresConnInfo b)
$csequence :: forall (m :: * -> *) a.
Monad m =>
PostgresConnInfo (m a) -> m (PostgresConnInfo a)
sequence :: forall (m :: * -> *) a.
Monad m =>
PostgresConnInfo (m a) -> m (PostgresConnInfo a)
Traversable)
pciDatabaseConn :: Lens' (PostgresConnInfo a) a
pciDatabaseConn :: forall a (f :: * -> *).
Functor f =>
(a -> f a) -> PostgresConnInfo a -> f (PostgresConnInfo a)
pciDatabaseConn = (PostgresConnInfo a -> a)
-> (PostgresConnInfo a -> a -> PostgresConnInfo a)
-> Lens (PostgresConnInfo a) (PostgresConnInfo a) a a
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens PostgresConnInfo a -> a
forall a. PostgresConnInfo a -> a
_pciDatabaseConn ((PostgresConnInfo a -> a -> PostgresConnInfo a)
-> Lens (PostgresConnInfo a) (PostgresConnInfo a) a a)
-> (PostgresConnInfo a -> a -> PostgresConnInfo a)
-> Lens (PostgresConnInfo a) (PostgresConnInfo a) a a
forall a b. (a -> b) -> a -> b
$ \PostgresConnInfo a
pci a
a -> PostgresConnInfo a
pci {_pciDatabaseConn :: a
_pciDatabaseConn = a
a}
pciRetries :: Lens' (PostgresConnInfo a) (Maybe Int)
pciRetries :: forall a (f :: * -> *).
Functor f =>
(Maybe Int -> f (Maybe Int))
-> PostgresConnInfo a -> f (PostgresConnInfo a)
pciRetries = (PostgresConnInfo a -> Maybe Int)
-> (PostgresConnInfo a -> Maybe Int -> PostgresConnInfo a)
-> Lens
(PostgresConnInfo a) (PostgresConnInfo a) (Maybe Int) (Maybe Int)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens PostgresConnInfo a -> Maybe Int
forall a. PostgresConnInfo a -> Maybe Int
_pciRetries ((PostgresConnInfo a -> Maybe Int -> PostgresConnInfo a)
-> Lens
(PostgresConnInfo a) (PostgresConnInfo a) (Maybe Int) (Maybe Int))
-> (PostgresConnInfo a -> Maybe Int -> PostgresConnInfo a)
-> Lens
(PostgresConnInfo a) (PostgresConnInfo a) (Maybe Int) (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \PostgresConnInfo a
pci Maybe Int
mi -> PostgresConnInfo a
pci {_pciRetries :: Maybe Int
_pciRetries = Maybe Int
mi}
data PostgresConnInfoRaw
= PGConnDatabaseUrl Template.Template
| PGConnDetails PostgresConnDetailsRaw
deriving (Int -> PostgresConnInfoRaw -> ShowS
[PostgresConnInfoRaw] -> ShowS
PostgresConnInfoRaw -> String
(Int -> PostgresConnInfoRaw -> ShowS)
-> (PostgresConnInfoRaw -> String)
-> ([PostgresConnInfoRaw] -> ShowS)
-> Show PostgresConnInfoRaw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PostgresConnInfoRaw -> ShowS
showsPrec :: Int -> PostgresConnInfoRaw -> ShowS
$cshow :: PostgresConnInfoRaw -> String
show :: PostgresConnInfoRaw -> String
$cshowList :: [PostgresConnInfoRaw] -> ShowS
showList :: [PostgresConnInfoRaw] -> ShowS
Show, PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool
(PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool)
-> (PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool)
-> Eq PostgresConnInfoRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool
== :: PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool
$c/= :: PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool
/= :: PostgresConnInfoRaw -> PostgresConnInfoRaw -> Bool
Eq)
mkUrlConnInfo :: String -> PostgresConnInfoRaw
mkUrlConnInfo :: String -> PostgresConnInfoRaw
mkUrlConnInfo = Template -> PostgresConnInfoRaw
PGConnDatabaseUrl (Template -> PostgresConnInfoRaw)
-> (String -> Template) -> String -> PostgresConnInfoRaw
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Template
Template.mkPlainTemplate (Text -> Template) -> (String -> Text) -> String -> Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
_PGConnDatabaseUrl :: Prism' PostgresConnInfoRaw Template.Template
_PGConnDatabaseUrl :: Prism' PostgresConnInfoRaw Template
_PGConnDatabaseUrl = (Template -> PostgresConnInfoRaw)
-> (PostgresConnInfoRaw -> Maybe Template)
-> Prism' PostgresConnInfoRaw Template
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Lens.prism' Template -> PostgresConnInfoRaw
PGConnDatabaseUrl ((PostgresConnInfoRaw -> Maybe Template)
-> Prism' PostgresConnInfoRaw Template)
-> (PostgresConnInfoRaw -> Maybe Template)
-> Prism' PostgresConnInfoRaw Template
forall a b. (a -> b) -> a -> b
$ \case
PGConnDatabaseUrl Template
template -> Template -> Maybe Template
forall a. a -> Maybe a
Just Template
template
PGConnDetails PostgresConnDetailsRaw
_ -> Maybe Template
forall a. Maybe a
Nothing
_PGConnDetails :: Prism' PostgresConnInfoRaw PostgresConnDetailsRaw
_PGConnDetails :: Prism' PostgresConnInfoRaw PostgresConnDetailsRaw
_PGConnDetails = (PostgresConnDetailsRaw -> PostgresConnInfoRaw)
-> (PostgresConnInfoRaw -> Maybe PostgresConnDetailsRaw)
-> Prism' PostgresConnInfoRaw PostgresConnDetailsRaw
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Lens.prism' PostgresConnDetailsRaw -> PostgresConnInfoRaw
PGConnDetails ((PostgresConnInfoRaw -> Maybe PostgresConnDetailsRaw)
-> Prism' PostgresConnInfoRaw PostgresConnDetailsRaw)
-> (PostgresConnInfoRaw -> Maybe PostgresConnDetailsRaw)
-> Prism' PostgresConnInfoRaw PostgresConnDetailsRaw
forall a b. (a -> b) -> a -> b
$ \case
PGConnDatabaseUrl Template
_ -> Maybe PostgresConnDetailsRaw
forall a. Maybe a
Nothing
PGConnDetails PostgresConnDetailsRaw
prcd -> PostgresConnDetailsRaw -> Maybe PostgresConnDetailsRaw
forall a. a -> Maybe a
Just PostgresConnDetailsRaw
prcd
rawConnDetailsToUrl :: PostgresConnDetailsRaw -> Template.Template
rawConnDetailsToUrl :: PostgresConnDetailsRaw -> Template
rawConnDetailsToUrl =
Text -> Template
Template.mkPlainTemplate (Text -> Template)
-> (PostgresConnDetailsRaw -> Text)
-> PostgresConnDetailsRaw
-> Template
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PostgresConnDetailsRaw -> Text
rawConnDetailsToUrlText
data PostgresConnDetailsRaw = PostgresConnDetailsRaw
{ PostgresConnDetailsRaw -> String
connHost :: String,
PostgresConnDetailsRaw -> Int
connPort :: Int,
PostgresConnDetailsRaw -> String
connUser :: String,
PostgresConnDetailsRaw -> String
connPassword :: String,
PostgresConnDetailsRaw -> String
connDatabase :: String,
PostgresConnDetailsRaw -> Maybe String
connOptions :: Maybe String
}
deriving (PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool
(PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool)
-> (PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool)
-> Eq PostgresConnDetailsRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool
== :: PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool
$c/= :: PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool
/= :: PostgresConnDetailsRaw -> PostgresConnDetailsRaw -> Bool
Eq, ReadPrec [PostgresConnDetailsRaw]
ReadPrec PostgresConnDetailsRaw
Int -> ReadS PostgresConnDetailsRaw
ReadS [PostgresConnDetailsRaw]
(Int -> ReadS PostgresConnDetailsRaw)
-> ReadS [PostgresConnDetailsRaw]
-> ReadPrec PostgresConnDetailsRaw
-> ReadPrec [PostgresConnDetailsRaw]
-> Read PostgresConnDetailsRaw
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS PostgresConnDetailsRaw
readsPrec :: Int -> ReadS PostgresConnDetailsRaw
$creadList :: ReadS [PostgresConnDetailsRaw]
readList :: ReadS [PostgresConnDetailsRaw]
$creadPrec :: ReadPrec PostgresConnDetailsRaw
readPrec :: ReadPrec PostgresConnDetailsRaw
$creadListPrec :: ReadPrec [PostgresConnDetailsRaw]
readListPrec :: ReadPrec [PostgresConnDetailsRaw]
Read, Int -> PostgresConnDetailsRaw -> ShowS
[PostgresConnDetailsRaw] -> ShowS
PostgresConnDetailsRaw -> String
(Int -> PostgresConnDetailsRaw -> ShowS)
-> (PostgresConnDetailsRaw -> String)
-> ([PostgresConnDetailsRaw] -> ShowS)
-> Show PostgresConnDetailsRaw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PostgresConnDetailsRaw -> ShowS
showsPrec :: Int -> PostgresConnDetailsRaw -> ShowS
$cshow :: PostgresConnDetailsRaw -> String
show :: PostgresConnDetailsRaw -> String
$cshowList :: [PostgresConnDetailsRaw] -> ShowS
showList :: [PostgresConnDetailsRaw] -> ShowS
Show)
instance FromJSON PostgresConnDetailsRaw where
parseJSON :: Value -> Parser PostgresConnDetailsRaw
parseJSON = String
-> (Object -> Parser PostgresConnDetailsRaw)
-> Value
-> Parser PostgresConnDetailsRaw
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"PostgresConnDetailsRaw" \Object
o -> do
String
connHost <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"host"
Int
connPort <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"port"
String
connUser <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user"
String
connPassword <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"password"
String
connDatabase <- Object
o Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"database"
Maybe String
connOptions <- Object
o Object -> Key -> Parser (Maybe String)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"options"
PostgresConnDetailsRaw -> Parser PostgresConnDetailsRaw
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PostgresConnDetailsRaw -> Parser PostgresConnDetailsRaw)
-> PostgresConnDetailsRaw -> Parser PostgresConnDetailsRaw
forall a b. (a -> b) -> a -> b
$ PostgresConnDetailsRaw {Int
String
Maybe String
connHost :: String
connPort :: Int
connUser :: String
connPassword :: String
connDatabase :: String
connOptions :: Maybe String
connHost :: String
connPort :: Int
connUser :: String
connPassword :: String
connDatabase :: String
connOptions :: Maybe String
..}
instance ToJSON PostgresConnDetailsRaw where
toJSON :: PostgresConnDetailsRaw -> Value
toJSON PostgresConnDetailsRaw {Int
String
Maybe String
connHost :: PostgresConnDetailsRaw -> String
connPort :: PostgresConnDetailsRaw -> Int
connUser :: PostgresConnDetailsRaw -> String
connPassword :: PostgresConnDetailsRaw -> String
connDatabase :: PostgresConnDetailsRaw -> String
connOptions :: PostgresConnDetailsRaw -> Maybe String
connHost :: String
connPort :: Int
connUser :: String
connPassword :: String
connDatabase :: String
connOptions :: Maybe String
..} =
[Pair] -> Value
J.object
([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [ Key
"host" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String
connHost,
Key
"port" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Int
connPort,
Key
"user" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String
connUser,
Key
"password" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String
connPassword,
Key
"database" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String
connDatabase
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
forall (f :: * -> *) a. Filterable f => f (Maybe a) -> f a
catMaybes [(String -> Pair) -> Maybe String -> Maybe Pair
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key
"options" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.=) Maybe String
connOptions]
rawConnDetailsToUrlText :: PostgresConnDetailsRaw -> Text
rawConnDetailsToUrlText :: PostgresConnDetailsRaw -> Text
rawConnDetailsToUrlText PostgresConnDetailsRaw {Int
String
Maybe String
connHost :: PostgresConnDetailsRaw -> String
connPort :: PostgresConnDetailsRaw -> Int
connUser :: PostgresConnDetailsRaw -> String
connPassword :: PostgresConnDetailsRaw -> String
connDatabase :: PostgresConnDetailsRaw -> String
connOptions :: PostgresConnDetailsRaw -> Maybe String
connHost :: String
connPort :: Int
connUser :: String
connPassword :: String
connDatabase :: String
connOptions :: Maybe String
..} =
String -> Text
Text.pack
(String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"postgresql://"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
connUser
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
connPassword
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"@"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
connHost
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
":"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
connPort
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"/"
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
connDatabase
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String -> ShowS -> Maybe String -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" (String
"?options=" String -> ShowS
forall a. Semigroup a => a -> a -> a
<>) Maybe String
connOptions
data HGECommand a
= HCServe a
| HCExport
| HCClean
| HCVersion
| HCDowngrade !DowngradeOptions
deriving (Int -> HGECommand a -> ShowS
[HGECommand a] -> ShowS
HGECommand a -> String
(Int -> HGECommand a -> ShowS)
-> (HGECommand a -> String)
-> ([HGECommand a] -> ShowS)
-> Show (HGECommand a)
forall a. Show a => Int -> HGECommand a -> ShowS
forall a. Show a => [HGECommand a] -> ShowS
forall a. Show a => HGECommand a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> HGECommand a -> ShowS
showsPrec :: Int -> HGECommand a -> ShowS
$cshow :: forall a. Show a => HGECommand a -> String
show :: HGECommand a -> String
$cshowList :: forall a. Show a => [HGECommand a] -> ShowS
showList :: [HGECommand a] -> ShowS
Show, HGECommand a -> HGECommand a -> Bool
(HGECommand a -> HGECommand a -> Bool)
-> (HGECommand a -> HGECommand a -> Bool) -> Eq (HGECommand a)
forall a. Eq a => HGECommand a -> HGECommand a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => HGECommand a -> HGECommand a -> Bool
== :: HGECommand a -> HGECommand a -> Bool
$c/= :: forall a. Eq a => HGECommand a -> HGECommand a -> Bool
/= :: HGECommand a -> HGECommand a -> Bool
Eq)
_HCServe :: Prism' (HGECommand a) a
_HCServe :: forall a (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f a) -> p (HGECommand a) (f (HGECommand a))
_HCServe = (a -> HGECommand a)
-> (HGECommand a -> Maybe a)
-> Prism (HGECommand a) (HGECommand a) a a
forall b s a. (b -> s) -> (s -> Maybe a) -> Prism s s a b
Lens.prism' a -> HGECommand a
forall a. a -> HGECommand a
HCServe \case
HCServe a
a -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
HGECommand a
_ -> Maybe a
forall a. Maybe a
Nothing
data ServeOptionsRaw impl = ServeOptionsRaw
{ forall impl. ServeOptionsRaw impl -> Maybe Port
rsoPort :: Maybe Port,
forall impl. ServeOptionsRaw impl -> Maybe HostPreference
rsoHost :: Maybe Warp.HostPreference,
forall impl. ServeOptionsRaw impl -> ConnParamsRaw
rsoConnParams :: ConnParamsRaw,
forall impl. ServeOptionsRaw impl -> Maybe TxIsolation
rsoTxIso :: Maybe Query.TxIsolation,
forall impl. ServeOptionsRaw impl -> Maybe AdminSecretHash
rsoAdminSecret :: Maybe Auth.AdminSecretHash,
forall impl. ServeOptionsRaw impl -> AuthHookRaw
rsoAuthHook :: AuthHookRaw,
forall impl. ServeOptionsRaw impl -> Maybe JWTConfig
rsoJwtSecret :: Maybe Auth.JWTConfig,
forall impl. ServeOptionsRaw impl -> Maybe RoleName
rsoUnAuthRole :: Maybe RoleName,
forall impl. ServeOptionsRaw impl -> Maybe CorsConfig
rsoCorsConfig :: Maybe Cors.CorsConfig,
forall impl. ServeOptionsRaw impl -> ConsoleStatus
rsoConsoleStatus :: ConsoleStatus,
forall impl. ServeOptionsRaw impl -> Maybe Text
rsoConsoleAssetsDir :: Maybe Text,
forall impl. ServeOptionsRaw impl -> Maybe Text
rsoConsoleSentryDsn :: Maybe Text,
forall impl. ServeOptionsRaw impl -> Maybe TelemetryStatus
rsoEnableTelemetry :: Maybe TelemetryStatus,
forall impl. ServeOptionsRaw impl -> WsReadCookieStatus
rsoWsReadCookie :: WsReadCookieStatus,
forall impl. ServeOptionsRaw impl -> StringifyNumbers
rsoStringifyNum :: Schema.Options.StringifyNumbers,
forall impl.
ServeOptionsRaw impl -> Maybe DangerouslyCollapseBooleans
rsoDangerousBooleanCollapse :: Maybe Schema.Options.DangerouslyCollapseBooleans,
forall impl. ServeOptionsRaw impl -> Maybe (HashSet API)
rsoEnabledAPIs :: Maybe (HashSet API),
forall impl. ServeOptionsRaw impl -> Maybe RefetchInterval
rsoMxRefetchInt :: Maybe Subscription.Options.RefetchInterval,
forall impl. ServeOptionsRaw impl -> Maybe BatchSize
rsoMxBatchSize :: Maybe Subscription.Options.BatchSize,
forall impl. ServeOptionsRaw impl -> Maybe RefetchInterval
rsoStreamingMxRefetchInt :: Maybe Subscription.Options.RefetchInterval,
forall impl. ServeOptionsRaw impl -> Maybe BatchSize
rsoStreamingMxBatchSize :: Maybe Subscription.Options.BatchSize,
forall impl. ServeOptionsRaw impl -> AllowListStatus
rsoEnableAllowList :: AllowListStatus,
forall impl.
ServeOptionsRaw impl -> Maybe (HashSet (EngineLogType impl))
rsoEnabledLogTypes :: Maybe (HashSet (Logging.EngineLogType impl)),
forall impl. ServeOptionsRaw impl -> Maybe LogLevel
rsoLogLevel :: Maybe Logging.LogLevel,
forall impl. ServeOptionsRaw impl -> DevModeStatus
rsoDevMode :: DevModeStatus,
forall impl.
ServeOptionsRaw impl -> Maybe AdminInternalErrorsStatus
rsoAdminInternalErrors :: Maybe AdminInternalErrorsStatus,
forall impl. ServeOptionsRaw impl -> Maybe (Refined Positive Int)
rsoEventsHttpPoolSize :: Maybe (Refined Positive Int),
forall impl.
ServeOptionsRaw impl -> Maybe (Refined NonNegative Milliseconds)
rsoEventsFetchInterval :: Maybe (Refined NonNegative Milliseconds),
forall impl. ServeOptionsRaw impl -> Maybe OptionalInterval
rsoAsyncActionsFetchInterval :: Maybe OptionalInterval,
forall impl. ServeOptionsRaw impl -> RemoteSchemaPermissions
rsoEnableRemoteSchemaPermissions :: Schema.Options.RemoteSchemaPermissions,
forall impl. ServeOptionsRaw impl -> CompressionOptions
rsoWebSocketCompression :: WebSockets.CompressionOptions,
forall impl. ServeOptionsRaw impl -> Maybe KeepAliveDelay
rsoWebSocketKeepAlive :: Maybe KeepAliveDelay,
forall impl. ServeOptionsRaw impl -> Maybe InferFunctionPermissions
rsoInferFunctionPermissions :: Maybe Schema.Options.InferFunctionPermissions,
forall impl. ServeOptionsRaw impl -> MaintenanceMode ()
rsoEnableMaintenanceMode :: Server.Types.MaintenanceMode (),
forall impl. ServeOptionsRaw impl -> Maybe OptionalInterval
rsoSchemaPollInterval :: Maybe OptionalInterval,
forall impl.
ServeOptionsRaw impl -> Maybe (HashSet ExperimentalFeature)
rsoExperimentalFeatures :: Maybe (HashSet Server.Types.ExperimentalFeature),
forall impl.
ServeOptionsRaw impl -> Maybe (Refined NonNegative Int)
rsoEventsFetchBatchSize :: Maybe (Refined NonNegative Int),
forall impl.
ServeOptionsRaw impl -> Maybe (Refined NonNegative Seconds)
rsoGracefulShutdownTimeout :: Maybe (Refined NonNegative Seconds),
forall impl. ServeOptionsRaw impl -> Maybe WSConnectionInitTimeout
rsoWebSocketConnectionInitTimeout :: Maybe WSConnectionInitTimeout,
forall impl. ServeOptionsRaw impl -> MetadataQueryLoggingMode
rsoEnableMetadataQueryLoggingEnv :: Server.Logging.MetadataQueryLoggingMode,
forall impl. ServeOptionsRaw impl -> Maybe NamingCase
rsoDefaultNamingConvention :: Maybe NamingCase,
forall impl. ServeOptionsRaw impl -> Maybe ExtensionsSchema
rsoExtensionsSchema :: Maybe MonadTx.ExtensionsSchema,
forall impl. ServeOptionsRaw impl -> Maybe MetadataDefaults
rsoMetadataDefaults :: Maybe MetadataDefaults,
forall impl. ServeOptionsRaw impl -> Maybe ApolloFederationStatus
rsoApolloFederationStatus :: Maybe Server.Types.ApolloFederationStatus,
forall impl.
ServeOptionsRaw impl -> Maybe CloseWebsocketsOnMetadataChangeStatus
rsoCloseWebsocketsOnMetadataChangeStatus :: Maybe Server.Types.CloseWebsocketsOnMetadataChangeStatus,
:: Maybe Int
}
data ConsoleStatus = ConsoleEnabled | ConsoleDisabled
deriving stock (Int -> ConsoleStatus -> ShowS
[ConsoleStatus] -> ShowS
ConsoleStatus -> String
(Int -> ConsoleStatus -> ShowS)
-> (ConsoleStatus -> String)
-> ([ConsoleStatus] -> ShowS)
-> Show ConsoleStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConsoleStatus -> ShowS
showsPrec :: Int -> ConsoleStatus -> ShowS
$cshow :: ConsoleStatus -> String
show :: ConsoleStatus -> String
$cshowList :: [ConsoleStatus] -> ShowS
showList :: [ConsoleStatus] -> ShowS
Show, ConsoleStatus -> ConsoleStatus -> Bool
(ConsoleStatus -> ConsoleStatus -> Bool)
-> (ConsoleStatus -> ConsoleStatus -> Bool) -> Eq ConsoleStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConsoleStatus -> ConsoleStatus -> Bool
== :: ConsoleStatus -> ConsoleStatus -> Bool
$c/= :: ConsoleStatus -> ConsoleStatus -> Bool
/= :: ConsoleStatus -> ConsoleStatus -> Bool
Eq, Eq ConsoleStatus
Eq ConsoleStatus
-> (ConsoleStatus -> ConsoleStatus -> Ordering)
-> (ConsoleStatus -> ConsoleStatus -> Bool)
-> (ConsoleStatus -> ConsoleStatus -> Bool)
-> (ConsoleStatus -> ConsoleStatus -> Bool)
-> (ConsoleStatus -> ConsoleStatus -> Bool)
-> (ConsoleStatus -> ConsoleStatus -> ConsoleStatus)
-> (ConsoleStatus -> ConsoleStatus -> ConsoleStatus)
-> Ord ConsoleStatus
ConsoleStatus -> ConsoleStatus -> Bool
ConsoleStatus -> ConsoleStatus -> Ordering
ConsoleStatus -> ConsoleStatus -> ConsoleStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: ConsoleStatus -> ConsoleStatus -> Ordering
compare :: ConsoleStatus -> ConsoleStatus -> Ordering
$c< :: ConsoleStatus -> ConsoleStatus -> Bool
< :: ConsoleStatus -> ConsoleStatus -> Bool
$c<= :: ConsoleStatus -> ConsoleStatus -> Bool
<= :: ConsoleStatus -> ConsoleStatus -> Bool
$c> :: ConsoleStatus -> ConsoleStatus -> Bool
> :: ConsoleStatus -> ConsoleStatus -> Bool
$c>= :: ConsoleStatus -> ConsoleStatus -> Bool
>= :: ConsoleStatus -> ConsoleStatus -> Bool
$cmax :: ConsoleStatus -> ConsoleStatus -> ConsoleStatus
max :: ConsoleStatus -> ConsoleStatus -> ConsoleStatus
$cmin :: ConsoleStatus -> ConsoleStatus -> ConsoleStatus
min :: ConsoleStatus -> ConsoleStatus -> ConsoleStatus
Ord, (forall x. ConsoleStatus -> Rep ConsoleStatus x)
-> (forall x. Rep ConsoleStatus x -> ConsoleStatus)
-> Generic ConsoleStatus
forall x. Rep ConsoleStatus x -> ConsoleStatus
forall x. ConsoleStatus -> Rep ConsoleStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConsoleStatus -> Rep ConsoleStatus x
from :: forall x. ConsoleStatus -> Rep ConsoleStatus x
$cto :: forall x. Rep ConsoleStatus x -> ConsoleStatus
to :: forall x. Rep ConsoleStatus x -> ConsoleStatus
Generic)
instance NFData ConsoleStatus
instance Hashable ConsoleStatus
isConsoleEnabled :: ConsoleStatus -> Bool
isConsoleEnabled :: ConsoleStatus -> Bool
isConsoleEnabled = \case
ConsoleStatus
ConsoleEnabled -> Bool
True
ConsoleStatus
ConsoleDisabled -> Bool
False
instance FromJSON ConsoleStatus where
parseJSON :: Value -> Parser ConsoleStatus
parseJSON = (Bool -> ConsoleStatus) -> Parser Bool -> Parser ConsoleStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ConsoleStatus -> ConsoleStatus -> Bool -> ConsoleStatus
forall a. a -> a -> Bool -> a
bool ConsoleStatus
ConsoleDisabled ConsoleStatus
ConsoleEnabled) (Parser Bool -> Parser ConsoleStatus)
-> (Value -> Parser Bool) -> Value -> Parser ConsoleStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON ConsoleStatus where
toJSON :: ConsoleStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (ConsoleStatus -> Bool) -> ConsoleStatus -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConsoleStatus -> Bool
isConsoleEnabled
data = AdminInternalErrorsEnabled | AdminInternalErrorsDisabled
deriving stock (Int -> AdminInternalErrorsStatus -> ShowS
[AdminInternalErrorsStatus] -> ShowS
AdminInternalErrorsStatus -> String
(Int -> AdminInternalErrorsStatus -> ShowS)
-> (AdminInternalErrorsStatus -> String)
-> ([AdminInternalErrorsStatus] -> ShowS)
-> Show AdminInternalErrorsStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AdminInternalErrorsStatus -> ShowS
showsPrec :: Int -> AdminInternalErrorsStatus -> ShowS
$cshow :: AdminInternalErrorsStatus -> String
show :: AdminInternalErrorsStatus -> String
$cshowList :: [AdminInternalErrorsStatus] -> ShowS
showList :: [AdminInternalErrorsStatus] -> ShowS
Show, AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
(AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> (AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> Eq AdminInternalErrorsStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
== :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
$c/= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
/= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
Eq, Eq AdminInternalErrorsStatus
Eq AdminInternalErrorsStatus
-> (AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> Ordering)
-> (AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> (AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> (AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> (AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool)
-> (AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus)
-> (AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus)
-> Ord AdminInternalErrorsStatus
AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Ordering
AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Ordering
compare :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Ordering
$c< :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
< :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
$c<= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
<= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
$c> :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
> :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
$c>= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
>= :: AdminInternalErrorsStatus -> AdminInternalErrorsStatus -> Bool
$cmax :: AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus
max :: AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus
$cmin :: AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus
min :: AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> AdminInternalErrorsStatus
Ord, (forall x.
AdminInternalErrorsStatus -> Rep AdminInternalErrorsStatus x)
-> (forall x.
Rep AdminInternalErrorsStatus x -> AdminInternalErrorsStatus)
-> Generic AdminInternalErrorsStatus
forall x.
Rep AdminInternalErrorsStatus x -> AdminInternalErrorsStatus
forall x.
AdminInternalErrorsStatus -> Rep AdminInternalErrorsStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
AdminInternalErrorsStatus -> Rep AdminInternalErrorsStatus x
from :: forall x.
AdminInternalErrorsStatus -> Rep AdminInternalErrorsStatus x
$cto :: forall x.
Rep AdminInternalErrorsStatus x -> AdminInternalErrorsStatus
to :: forall x.
Rep AdminInternalErrorsStatus x -> AdminInternalErrorsStatus
Generic)
instance NFData AdminInternalErrorsStatus
instance Hashable AdminInternalErrorsStatus
isAdminInternalErrorsEnabled :: AdminInternalErrorsStatus -> Bool
isAdminInternalErrorsEnabled :: AdminInternalErrorsStatus -> Bool
isAdminInternalErrorsEnabled = \case
AdminInternalErrorsStatus
AdminInternalErrorsEnabled -> Bool
True
AdminInternalErrorsStatus
AdminInternalErrorsDisabled -> Bool
False
instance FromJSON AdminInternalErrorsStatus where
parseJSON :: Value -> Parser AdminInternalErrorsStatus
parseJSON = (Bool -> AdminInternalErrorsStatus)
-> Parser Bool -> Parser AdminInternalErrorsStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AdminInternalErrorsStatus
-> AdminInternalErrorsStatus -> Bool -> AdminInternalErrorsStatus
forall a. a -> a -> Bool -> a
bool AdminInternalErrorsStatus
AdminInternalErrorsDisabled AdminInternalErrorsStatus
AdminInternalErrorsEnabled) (Parser Bool -> Parser AdminInternalErrorsStatus)
-> (Value -> Parser Bool)
-> Value
-> Parser AdminInternalErrorsStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON AdminInternalErrorsStatus where
toJSON :: AdminInternalErrorsStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (AdminInternalErrorsStatus -> Bool)
-> AdminInternalErrorsStatus
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AdminInternalErrorsStatus -> Bool
isAdminInternalErrorsEnabled
isWebSocketCompressionEnabled :: WebSockets.CompressionOptions -> Bool
isWebSocketCompressionEnabled :: CompressionOptions -> Bool
isWebSocketCompressionEnabled = \case
WebSockets.PermessageDeflateCompression PermessageDeflate
_ -> Bool
True
CompressionOptions
WebSockets.NoCompression -> Bool
False
data AllowListStatus = AllowListEnabled | AllowListDisabled
deriving stock (Int -> AllowListStatus -> ShowS
[AllowListStatus] -> ShowS
AllowListStatus -> String
(Int -> AllowListStatus -> ShowS)
-> (AllowListStatus -> String)
-> ([AllowListStatus] -> ShowS)
-> Show AllowListStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AllowListStatus -> ShowS
showsPrec :: Int -> AllowListStatus -> ShowS
$cshow :: AllowListStatus -> String
show :: AllowListStatus -> String
$cshowList :: [AllowListStatus] -> ShowS
showList :: [AllowListStatus] -> ShowS
Show, AllowListStatus -> AllowListStatus -> Bool
(AllowListStatus -> AllowListStatus -> Bool)
-> (AllowListStatus -> AllowListStatus -> Bool)
-> Eq AllowListStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AllowListStatus -> AllowListStatus -> Bool
== :: AllowListStatus -> AllowListStatus -> Bool
$c/= :: AllowListStatus -> AllowListStatus -> Bool
/= :: AllowListStatus -> AllowListStatus -> Bool
Eq, Eq AllowListStatus
Eq AllowListStatus
-> (AllowListStatus -> AllowListStatus -> Ordering)
-> (AllowListStatus -> AllowListStatus -> Bool)
-> (AllowListStatus -> AllowListStatus -> Bool)
-> (AllowListStatus -> AllowListStatus -> Bool)
-> (AllowListStatus -> AllowListStatus -> Bool)
-> (AllowListStatus -> AllowListStatus -> AllowListStatus)
-> (AllowListStatus -> AllowListStatus -> AllowListStatus)
-> Ord AllowListStatus
AllowListStatus -> AllowListStatus -> Bool
AllowListStatus -> AllowListStatus -> Ordering
AllowListStatus -> AllowListStatus -> AllowListStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: AllowListStatus -> AllowListStatus -> Ordering
compare :: AllowListStatus -> AllowListStatus -> Ordering
$c< :: AllowListStatus -> AllowListStatus -> Bool
< :: AllowListStatus -> AllowListStatus -> Bool
$c<= :: AllowListStatus -> AllowListStatus -> Bool
<= :: AllowListStatus -> AllowListStatus -> Bool
$c> :: AllowListStatus -> AllowListStatus -> Bool
> :: AllowListStatus -> AllowListStatus -> Bool
$c>= :: AllowListStatus -> AllowListStatus -> Bool
>= :: AllowListStatus -> AllowListStatus -> Bool
$cmax :: AllowListStatus -> AllowListStatus -> AllowListStatus
max :: AllowListStatus -> AllowListStatus -> AllowListStatus
$cmin :: AllowListStatus -> AllowListStatus -> AllowListStatus
min :: AllowListStatus -> AllowListStatus -> AllowListStatus
Ord, (forall x. AllowListStatus -> Rep AllowListStatus x)
-> (forall x. Rep AllowListStatus x -> AllowListStatus)
-> Generic AllowListStatus
forall x. Rep AllowListStatus x -> AllowListStatus
forall x. AllowListStatus -> Rep AllowListStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AllowListStatus -> Rep AllowListStatus x
from :: forall x. AllowListStatus -> Rep AllowListStatus x
$cto :: forall x. Rep AllowListStatus x -> AllowListStatus
to :: forall x. Rep AllowListStatus x -> AllowListStatus
Generic)
instance NFData AllowListStatus
instance Hashable AllowListStatus
isAllowListEnabled :: AllowListStatus -> Bool
isAllowListEnabled :: AllowListStatus -> Bool
isAllowListEnabled = \case
AllowListStatus
AllowListEnabled -> Bool
True
AllowListStatus
AllowListDisabled -> Bool
False
instance FromJSON AllowListStatus where
parseJSON :: Value -> Parser AllowListStatus
parseJSON = (Bool -> AllowListStatus) -> Parser Bool -> Parser AllowListStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (AllowListStatus -> AllowListStatus -> Bool -> AllowListStatus
forall a. a -> a -> Bool -> a
bool AllowListStatus
AllowListDisabled AllowListStatus
AllowListEnabled) (Parser Bool -> Parser AllowListStatus)
-> (Value -> Parser Bool) -> Value -> Parser AllowListStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON AllowListStatus where
toJSON :: AllowListStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (AllowListStatus -> Bool) -> AllowListStatus -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AllowListStatus -> Bool
isAllowListEnabled
data DevModeStatus = DevModeEnabled | DevModeDisabled
deriving stock (Int -> DevModeStatus -> ShowS
[DevModeStatus] -> ShowS
DevModeStatus -> String
(Int -> DevModeStatus -> ShowS)
-> (DevModeStatus -> String)
-> ([DevModeStatus] -> ShowS)
-> Show DevModeStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DevModeStatus -> ShowS
showsPrec :: Int -> DevModeStatus -> ShowS
$cshow :: DevModeStatus -> String
show :: DevModeStatus -> String
$cshowList :: [DevModeStatus] -> ShowS
showList :: [DevModeStatus] -> ShowS
Show, DevModeStatus -> DevModeStatus -> Bool
(DevModeStatus -> DevModeStatus -> Bool)
-> (DevModeStatus -> DevModeStatus -> Bool) -> Eq DevModeStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DevModeStatus -> DevModeStatus -> Bool
== :: DevModeStatus -> DevModeStatus -> Bool
$c/= :: DevModeStatus -> DevModeStatus -> Bool
/= :: DevModeStatus -> DevModeStatus -> Bool
Eq, Eq DevModeStatus
Eq DevModeStatus
-> (DevModeStatus -> DevModeStatus -> Ordering)
-> (DevModeStatus -> DevModeStatus -> Bool)
-> (DevModeStatus -> DevModeStatus -> Bool)
-> (DevModeStatus -> DevModeStatus -> Bool)
-> (DevModeStatus -> DevModeStatus -> Bool)
-> (DevModeStatus -> DevModeStatus -> DevModeStatus)
-> (DevModeStatus -> DevModeStatus -> DevModeStatus)
-> Ord DevModeStatus
DevModeStatus -> DevModeStatus -> Bool
DevModeStatus -> DevModeStatus -> Ordering
DevModeStatus -> DevModeStatus -> DevModeStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DevModeStatus -> DevModeStatus -> Ordering
compare :: DevModeStatus -> DevModeStatus -> Ordering
$c< :: DevModeStatus -> DevModeStatus -> Bool
< :: DevModeStatus -> DevModeStatus -> Bool
$c<= :: DevModeStatus -> DevModeStatus -> Bool
<= :: DevModeStatus -> DevModeStatus -> Bool
$c> :: DevModeStatus -> DevModeStatus -> Bool
> :: DevModeStatus -> DevModeStatus -> Bool
$c>= :: DevModeStatus -> DevModeStatus -> Bool
>= :: DevModeStatus -> DevModeStatus -> Bool
$cmax :: DevModeStatus -> DevModeStatus -> DevModeStatus
max :: DevModeStatus -> DevModeStatus -> DevModeStatus
$cmin :: DevModeStatus -> DevModeStatus -> DevModeStatus
min :: DevModeStatus -> DevModeStatus -> DevModeStatus
Ord, (forall x. DevModeStatus -> Rep DevModeStatus x)
-> (forall x. Rep DevModeStatus x -> DevModeStatus)
-> Generic DevModeStatus
forall x. Rep DevModeStatus x -> DevModeStatus
forall x. DevModeStatus -> Rep DevModeStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DevModeStatus -> Rep DevModeStatus x
from :: forall x. DevModeStatus -> Rep DevModeStatus x
$cto :: forall x. Rep DevModeStatus x -> DevModeStatus
to :: forall x. Rep DevModeStatus x -> DevModeStatus
Generic)
instance NFData DevModeStatus
instance Hashable DevModeStatus
isDevModeEnabled :: DevModeStatus -> Bool
isDevModeEnabled :: DevModeStatus -> Bool
isDevModeEnabled = \case
DevModeStatus
DevModeEnabled -> Bool
True
DevModeStatus
DevModeDisabled -> Bool
False
instance FromJSON DevModeStatus where
parseJSON :: Value -> Parser DevModeStatus
parseJSON = (Bool -> DevModeStatus) -> Parser Bool -> Parser DevModeStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DevModeStatus -> DevModeStatus -> Bool -> DevModeStatus
forall a. a -> a -> Bool -> a
bool DevModeStatus
DevModeDisabled DevModeStatus
DevModeEnabled) (Parser Bool -> Parser DevModeStatus)
-> (Value -> Parser Bool) -> Value -> Parser DevModeStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON DevModeStatus where
toJSON :: DevModeStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (DevModeStatus -> Bool) -> DevModeStatus -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DevModeStatus -> Bool
isDevModeEnabled
data TelemetryStatus = TelemetryEnabled | TelemetryDisabled
deriving stock (Int -> TelemetryStatus -> ShowS
[TelemetryStatus] -> ShowS
TelemetryStatus -> String
(Int -> TelemetryStatus -> ShowS)
-> (TelemetryStatus -> String)
-> ([TelemetryStatus] -> ShowS)
-> Show TelemetryStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TelemetryStatus -> ShowS
showsPrec :: Int -> TelemetryStatus -> ShowS
$cshow :: TelemetryStatus -> String
show :: TelemetryStatus -> String
$cshowList :: [TelemetryStatus] -> ShowS
showList :: [TelemetryStatus] -> ShowS
Show, TelemetryStatus -> TelemetryStatus -> Bool
(TelemetryStatus -> TelemetryStatus -> Bool)
-> (TelemetryStatus -> TelemetryStatus -> Bool)
-> Eq TelemetryStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TelemetryStatus -> TelemetryStatus -> Bool
== :: TelemetryStatus -> TelemetryStatus -> Bool
$c/= :: TelemetryStatus -> TelemetryStatus -> Bool
/= :: TelemetryStatus -> TelemetryStatus -> Bool
Eq, Eq TelemetryStatus
Eq TelemetryStatus
-> (TelemetryStatus -> TelemetryStatus -> Ordering)
-> (TelemetryStatus -> TelemetryStatus -> Bool)
-> (TelemetryStatus -> TelemetryStatus -> Bool)
-> (TelemetryStatus -> TelemetryStatus -> Bool)
-> (TelemetryStatus -> TelemetryStatus -> Bool)
-> (TelemetryStatus -> TelemetryStatus -> TelemetryStatus)
-> (TelemetryStatus -> TelemetryStatus -> TelemetryStatus)
-> Ord TelemetryStatus
TelemetryStatus -> TelemetryStatus -> Bool
TelemetryStatus -> TelemetryStatus -> Ordering
TelemetryStatus -> TelemetryStatus -> TelemetryStatus
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TelemetryStatus -> TelemetryStatus -> Ordering
compare :: TelemetryStatus -> TelemetryStatus -> Ordering
$c< :: TelemetryStatus -> TelemetryStatus -> Bool
< :: TelemetryStatus -> TelemetryStatus -> Bool
$c<= :: TelemetryStatus -> TelemetryStatus -> Bool
<= :: TelemetryStatus -> TelemetryStatus -> Bool
$c> :: TelemetryStatus -> TelemetryStatus -> Bool
> :: TelemetryStatus -> TelemetryStatus -> Bool
$c>= :: TelemetryStatus -> TelemetryStatus -> Bool
>= :: TelemetryStatus -> TelemetryStatus -> Bool
$cmax :: TelemetryStatus -> TelemetryStatus -> TelemetryStatus
max :: TelemetryStatus -> TelemetryStatus -> TelemetryStatus
$cmin :: TelemetryStatus -> TelemetryStatus -> TelemetryStatus
min :: TelemetryStatus -> TelemetryStatus -> TelemetryStatus
Ord, (forall x. TelemetryStatus -> Rep TelemetryStatus x)
-> (forall x. Rep TelemetryStatus x -> TelemetryStatus)
-> Generic TelemetryStatus
forall x. Rep TelemetryStatus x -> TelemetryStatus
forall x. TelemetryStatus -> Rep TelemetryStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TelemetryStatus -> Rep TelemetryStatus x
from :: forall x. TelemetryStatus -> Rep TelemetryStatus x
$cto :: forall x. Rep TelemetryStatus x -> TelemetryStatus
to :: forall x. Rep TelemetryStatus x -> TelemetryStatus
Generic)
instance NFData TelemetryStatus
instance Hashable TelemetryStatus
isTelemetryEnabled :: TelemetryStatus -> Bool
isTelemetryEnabled :: TelemetryStatus -> Bool
isTelemetryEnabled = \case
TelemetryStatus
TelemetryEnabled -> Bool
True
TelemetryStatus
TelemetryDisabled -> Bool
False
instance FromJSON TelemetryStatus where
parseJSON :: Value -> Parser TelemetryStatus
parseJSON = (Bool -> TelemetryStatus) -> Parser Bool -> Parser TelemetryStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TelemetryStatus -> TelemetryStatus -> Bool -> TelemetryStatus
forall a. a -> a -> Bool -> a
bool TelemetryStatus
TelemetryDisabled TelemetryStatus
TelemetryEnabled) (Parser Bool -> Parser TelemetryStatus)
-> (Value -> Parser Bool) -> Value -> Parser TelemetryStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON TelemetryStatus where
toJSON :: TelemetryStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (TelemetryStatus -> Bool) -> TelemetryStatus -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TelemetryStatus -> Bool
isTelemetryEnabled
data WsReadCookieStatus = WsReadCookieEnabled | WsReadCookieDisabled
deriving stock (Int -> WsReadCookieStatus -> ShowS
[WsReadCookieStatus] -> ShowS
WsReadCookieStatus -> String
(Int -> WsReadCookieStatus -> ShowS)
-> (WsReadCookieStatus -> String)
-> ([WsReadCookieStatus] -> ShowS)
-> Show WsReadCookieStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WsReadCookieStatus -> ShowS
showsPrec :: Int -> WsReadCookieStatus -> ShowS
$cshow :: WsReadCookieStatus -> String
show :: WsReadCookieStatus -> String
$cshowList :: [WsReadCookieStatus] -> ShowS
showList :: [WsReadCookieStatus] -> ShowS
Show, WsReadCookieStatus -> WsReadCookieStatus -> Bool
(WsReadCookieStatus -> WsReadCookieStatus -> Bool)
-> (WsReadCookieStatus -> WsReadCookieStatus -> Bool)
-> Eq WsReadCookieStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WsReadCookieStatus -> WsReadCookieStatus -> Bool
== :: WsReadCookieStatus -> WsReadCookieStatus -> Bool
$c/= :: WsReadCookieStatus -> WsReadCookieStatus -> Bool
/= :: WsReadCookieStatus -> WsReadCookieStatus -> Bool
Eq, (forall x. WsReadCookieStatus -> Rep WsReadCookieStatus x)
-> (forall x. Rep WsReadCookieStatus x -> WsReadCookieStatus)
-> Generic WsReadCookieStatus
forall x. Rep WsReadCookieStatus x -> WsReadCookieStatus
forall x. WsReadCookieStatus -> Rep WsReadCookieStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WsReadCookieStatus -> Rep WsReadCookieStatus x
from :: forall x. WsReadCookieStatus -> Rep WsReadCookieStatus x
$cto :: forall x. Rep WsReadCookieStatus x -> WsReadCookieStatus
to :: forall x. Rep WsReadCookieStatus x -> WsReadCookieStatus
Generic)
instance NFData WsReadCookieStatus
instance Hashable WsReadCookieStatus
isWsReadCookieEnabled :: WsReadCookieStatus -> Bool
isWsReadCookieEnabled :: WsReadCookieStatus -> Bool
isWsReadCookieEnabled = \case
WsReadCookieStatus
WsReadCookieEnabled -> Bool
True
WsReadCookieStatus
WsReadCookieDisabled -> Bool
False
instance FromJSON WsReadCookieStatus where
parseJSON :: Value -> Parser WsReadCookieStatus
parseJSON = (Bool -> WsReadCookieStatus)
-> Parser Bool -> Parser WsReadCookieStatus
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (WsReadCookieStatus
-> WsReadCookieStatus -> Bool -> WsReadCookieStatus
forall a. a -> a -> Bool -> a
bool WsReadCookieStatus
WsReadCookieDisabled WsReadCookieStatus
WsReadCookieEnabled) (Parser Bool -> Parser WsReadCookieStatus)
-> (Value -> Parser Bool) -> Value -> Parser WsReadCookieStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
J.parseJSON
instance ToJSON WsReadCookieStatus where
toJSON :: WsReadCookieStatus -> Value
toJSON = Bool -> Value
forall a. ToJSON a => a -> Value
J.toJSON (Bool -> Value)
-> (WsReadCookieStatus -> Bool) -> WsReadCookieStatus -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WsReadCookieStatus -> Bool
isWsReadCookieEnabled
newtype Port = Port {Port -> Int
_getPort :: Int}
deriving stock (Int -> Port -> ShowS
[Port] -> ShowS
Port -> String
(Int -> Port -> ShowS)
-> (Port -> String) -> ([Port] -> ShowS) -> Show Port
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Port -> ShowS
showsPrec :: Int -> Port -> ShowS
$cshow :: Port -> String
show :: Port -> String
$cshowList :: [Port] -> ShowS
showList :: [Port] -> ShowS
Show, Port -> Port -> Bool
(Port -> Port -> Bool) -> (Port -> Port -> Bool) -> Eq Port
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Port -> Port -> Bool
== :: Port -> Port -> Bool
$c/= :: Port -> Port -> Bool
/= :: Port -> Port -> Bool
Eq, Eq Port
Eq Port
-> (Port -> Port -> Ordering)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Bool)
-> (Port -> Port -> Port)
-> (Port -> Port -> Port)
-> Ord Port
Port -> Port -> Bool
Port -> Port -> Ordering
Port -> Port -> Port
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Port -> Port -> Ordering
compare :: Port -> Port -> Ordering
$c< :: Port -> Port -> Bool
< :: Port -> Port -> Bool
$c<= :: Port -> Port -> Bool
<= :: Port -> Port -> Bool
$c> :: Port -> Port -> Bool
> :: Port -> Port -> Bool
$c>= :: Port -> Port -> Bool
>= :: Port -> Port -> Bool
$cmax :: Port -> Port -> Port
max :: Port -> Port -> Port
$cmin :: Port -> Port -> Port
min :: Port -> Port -> Port
Ord, (forall x. Port -> Rep Port x)
-> (forall x. Rep Port x -> Port) -> Generic Port
forall x. Rep Port x -> Port
forall x. Port -> Rep Port x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Port -> Rep Port x
from :: forall x. Port -> Rep Port x
$cto :: forall x. Rep Port x -> Port
to :: forall x. Rep Port x -> Port
Generic)
deriving newtype ([Port] -> Value
[Port] -> Encoding
Port -> Value
Port -> Encoding
(Port -> Value)
-> (Port -> Encoding)
-> ([Port] -> Value)
-> ([Port] -> Encoding)
-> ToJSON Port
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
$ctoJSON :: Port -> Value
toJSON :: Port -> Value
$ctoEncoding :: Port -> Encoding
toEncoding :: Port -> Encoding
$ctoJSONList :: [Port] -> Value
toJSONList :: [Port] -> Value
$ctoEncodingList :: [Port] -> Encoding
toEncodingList :: [Port] -> Encoding
ToJSON, Port -> ()
(Port -> ()) -> NFData Port
forall a. (a -> ()) -> NFData a
$crnf :: Port -> ()
rnf :: Port -> ()
NFData, Eq Port
Eq Port -> (Int -> Port -> Int) -> (Port -> Int) -> Hashable Port
Int -> Port -> Int
Port -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Port -> Int
hashWithSalt :: Int -> Port -> Int
$chash :: Port -> Int
hash :: Port -> Int
Hashable)
mkPort :: Int -> Maybe Port
mkPort :: Int -> Maybe Port
mkPort Int
x = case Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
65536 of
Bool
True -> Port -> Maybe Port
forall a. a -> Maybe a
Just (Port -> Maybe Port) -> Port -> Maybe Port
forall a b. (a -> b) -> a -> b
$ Int -> Port
Port Int
x
Bool
False -> Maybe Port
forall a. Maybe a
Nothing
unsafePort :: Int -> Port
unsafePort :: Int -> Port
unsafePort = Int -> Port
Port
instance FromJSON Port where
parseJSON :: Value -> Parser Port
parseJSON = String -> (Scientific -> Parser Port) -> Value -> Parser Port
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
J.withScientific String
"Int" ((Scientific -> Parser Port) -> Value -> Parser Port)
-> (Scientific -> Parser Port) -> Value -> Parser Port
forall a b. (a -> b) -> a -> b
$ \Scientific
t -> do
case Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
> Scientific
0 Bool -> Bool -> Bool
&& Scientific
t Scientific -> Scientific -> Bool
forall a. Ord a => a -> a -> Bool
< Scientific
65536 of
Bool
True -> Parser Port -> (Int -> Parser Port) -> Maybe Int -> Parser Port
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Parser Port
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"integer passed is out of bounds") (Port -> Parser Port
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Port -> Parser Port) -> (Int -> Port) -> Int -> Parser Port
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Port
Port) (Maybe Int -> Parser Port) -> Maybe Int -> Parser Port
forall a b. (a -> b) -> a -> b
$ Scientific -> Maybe Int
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
Scientific.toBoundedInteger Scientific
t
Bool
False -> String -> Parser Port
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"integer passed is out of bounds"
data API
= METADATA
| GRAPHQL
| PGDUMP
| DEVELOPER
| CONFIG
| METRICS
deriving (Int -> API -> ShowS
[API] -> ShowS
API -> String
(Int -> API -> ShowS)
-> (API -> String) -> ([API] -> ShowS) -> Show API
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> API -> ShowS
showsPrec :: Int -> API -> ShowS
$cshow :: API -> String
show :: API -> String
$cshowList :: [API] -> ShowS
showList :: [API] -> ShowS
Show, API -> API -> Bool
(API -> API -> Bool) -> (API -> API -> Bool) -> Eq API
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: API -> API -> Bool
== :: API -> API -> Bool
$c/= :: API -> API -> Bool
/= :: API -> API -> Bool
Eq, ReadPrec [API]
ReadPrec API
Int -> ReadS API
ReadS [API]
(Int -> ReadS API)
-> ReadS [API] -> ReadPrec API -> ReadPrec [API] -> Read API
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS API
readsPrec :: Int -> ReadS API
$creadList :: ReadS [API]
readList :: ReadS [API]
$creadPrec :: ReadPrec API
readPrec :: ReadPrec API
$creadListPrec :: ReadPrec [API]
readListPrec :: ReadPrec [API]
Read, (forall x. API -> Rep API x)
-> (forall x. Rep API x -> API) -> Generic API
forall x. Rep API x -> API
forall x. API -> Rep API x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. API -> Rep API x
from :: forall x. API -> Rep API x
$cto :: forall x. Rep API x -> API
to :: forall x. Rep API x -> API
Generic)
instance FromJSON API where
parseJSON :: Value -> Parser API
parseJSON = String -> (Text -> Parser API) -> Value -> Parser API
forall a. String -> (Text -> Parser a) -> Value -> Parser a
J.withText String
"API" \case
Text
"metadata" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
METADATA
Text
"graphql" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
GRAPHQL
Text
"pgdump" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
PGDUMP
Text
"developer" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
DEVELOPER
Text
"config" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
CONFIG
Text
"metrics" -> API -> Parser API
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure API
METRICS
Text
x -> String -> Parser API
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser API) -> String -> Parser API
forall a b. (a -> b) -> a -> b
$ String
"unexpected string '" String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
x String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"'."
instance ToJSON API where
toJSON :: API -> Value
toJSON = \case
API
METADATA -> Text -> Value
J.String Text
"metadata"
API
GRAPHQL -> Text -> Value
J.String Text
"graphql"
API
PGDUMP -> Text -> Value
J.String Text
"pgdump"
API
DEVELOPER -> Text -> Value
J.String Text
"developer"
API
CONFIG -> Text -> Value
J.String Text
"config"
API
METRICS -> Text -> Value
J.String Text
"metrics"
instance Hashable API
data AuthHookRaw = AuthHookRaw
{ AuthHookRaw -> Maybe Text
ahrUrl :: Maybe Text,
AuthHookRaw -> Maybe AuthHookType
ahrType :: Maybe Auth.AuthHookType,
AuthHookRaw -> Maybe Bool
ahrSendRequestBody :: Maybe Bool
}
data OptionalInterval
=
Skip
|
Interval (Refined NonNegative Milliseconds)
deriving (Int -> OptionalInterval -> ShowS
[OptionalInterval] -> ShowS
OptionalInterval -> String
(Int -> OptionalInterval -> ShowS)
-> (OptionalInterval -> String)
-> ([OptionalInterval] -> ShowS)
-> Show OptionalInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OptionalInterval -> ShowS
showsPrec :: Int -> OptionalInterval -> ShowS
$cshow :: OptionalInterval -> String
show :: OptionalInterval -> String
$cshowList :: [OptionalInterval] -> ShowS
showList :: [OptionalInterval] -> ShowS
Show, OptionalInterval -> OptionalInterval -> Bool
(OptionalInterval -> OptionalInterval -> Bool)
-> (OptionalInterval -> OptionalInterval -> Bool)
-> Eq OptionalInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OptionalInterval -> OptionalInterval -> Bool
== :: OptionalInterval -> OptionalInterval -> Bool
$c/= :: OptionalInterval -> OptionalInterval -> Bool
/= :: OptionalInterval -> OptionalInterval -> Bool
Eq)
msToOptionalInterval :: Refined NonNegative Milliseconds -> OptionalInterval
msToOptionalInterval :: Refined NonNegative Milliseconds -> OptionalInterval
msToOptionalInterval = \case
(Refined NonNegative Milliseconds -> Milliseconds
forall {k} (p :: k) x. Refined p x -> x
unrefine -> Milliseconds
0) -> OptionalInterval
Skip
Refined NonNegative Milliseconds
s -> Refined NonNegative Milliseconds -> OptionalInterval
Interval Refined NonNegative Milliseconds
s
instance FromJSON OptionalInterval where
parseJSON :: Value -> Parser OptionalInterval
parseJSON Value
v = Refined NonNegative Milliseconds -> OptionalInterval
msToOptionalInterval (Refined NonNegative Milliseconds -> OptionalInterval)
-> Parser (Refined NonNegative Milliseconds)
-> Parser OptionalInterval
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser (Refined NonNegative Milliseconds)
forall a. FromJSON a => Value -> Parser a
J.parseJSON Value
v
instance ToJSON OptionalInterval where
toJSON :: OptionalInterval -> Value
toJSON = \case
OptionalInterval
Skip -> forall a. ToJSON a => a -> Value
J.toJSON @Milliseconds Milliseconds
0
Interval Refined NonNegative Milliseconds
s -> Refined NonNegative Milliseconds -> Value
forall a. ToJSON a => a -> Value
J.toJSON Refined NonNegative Milliseconds
s
data ConnParamsRaw = ConnParamsRaw
{
ConnParamsRaw -> Maybe (Refined NonNegative Int)
rcpStripes :: Maybe (Refined NonNegative Int),
ConnParamsRaw -> Maybe (Refined NonNegative Int)
rcpConns :: Maybe (Refined NonNegative Int),
ConnParamsRaw -> Maybe (Refined NonNegative Int)
rcpIdleTime :: Maybe (Refined NonNegative Int),
ConnParamsRaw -> Maybe (Refined NonNegative NominalDiffTime)
rcpConnLifetime :: Maybe (Refined NonNegative Time.NominalDiffTime),
ConnParamsRaw -> Maybe Bool
rcpAllowPrepare :: Maybe Bool,
ConnParamsRaw -> Maybe (Refined NonNegative NominalDiffTime)
rcpPoolTimeout :: Maybe (Refined NonNegative Time.NominalDiffTime)
}
deriving (Int -> ConnParamsRaw -> ShowS
[ConnParamsRaw] -> ShowS
ConnParamsRaw -> String
(Int -> ConnParamsRaw -> ShowS)
-> (ConnParamsRaw -> String)
-> ([ConnParamsRaw] -> ShowS)
-> Show ConnParamsRaw
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnParamsRaw -> ShowS
showsPrec :: Int -> ConnParamsRaw -> ShowS
$cshow :: ConnParamsRaw -> String
show :: ConnParamsRaw -> String
$cshowList :: [ConnParamsRaw] -> ShowS
showList :: [ConnParamsRaw] -> ShowS
Show, ConnParamsRaw -> ConnParamsRaw -> Bool
(ConnParamsRaw -> ConnParamsRaw -> Bool)
-> (ConnParamsRaw -> ConnParamsRaw -> Bool) -> Eq ConnParamsRaw
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConnParamsRaw -> ConnParamsRaw -> Bool
== :: ConnParamsRaw -> ConnParamsRaw -> Bool
$c/= :: ConnParamsRaw -> ConnParamsRaw -> Bool
/= :: ConnParamsRaw -> ConnParamsRaw -> Bool
Eq)
newtype KeepAliveDelay = KeepAliveDelay {KeepAliveDelay -> Refined NonNegative Seconds
unKeepAliveDelay :: Refined NonNegative Seconds}
deriving (KeepAliveDelay -> KeepAliveDelay -> Bool
(KeepAliveDelay -> KeepAliveDelay -> Bool)
-> (KeepAliveDelay -> KeepAliveDelay -> Bool) -> Eq KeepAliveDelay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeepAliveDelay -> KeepAliveDelay -> Bool
== :: KeepAliveDelay -> KeepAliveDelay -> Bool
$c/= :: KeepAliveDelay -> KeepAliveDelay -> Bool
/= :: KeepAliveDelay -> KeepAliveDelay -> Bool
Eq, Int -> KeepAliveDelay -> ShowS
[KeepAliveDelay] -> ShowS
KeepAliveDelay -> String
(Int -> KeepAliveDelay -> ShowS)
-> (KeepAliveDelay -> String)
-> ([KeepAliveDelay] -> ShowS)
-> Show KeepAliveDelay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> KeepAliveDelay -> ShowS
showsPrec :: Int -> KeepAliveDelay -> ShowS
$cshow :: KeepAliveDelay -> String
show :: KeepAliveDelay -> String
$cshowList :: [KeepAliveDelay] -> ShowS
showList :: [KeepAliveDelay] -> ShowS
Show)
instance FromJSON KeepAliveDelay where
parseJSON :: Value -> Parser KeepAliveDelay
parseJSON = String
-> (Object -> Parser KeepAliveDelay)
-> Value
-> Parser KeepAliveDelay
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"KeepAliveDelay" \Object
o -> do
Refined NonNegative Seconds
unKeepAliveDelay <- Object
o Object -> Key -> Parser (Refined NonNegative Seconds)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"keep_alive_delay"
KeepAliveDelay -> Parser KeepAliveDelay
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (KeepAliveDelay -> Parser KeepAliveDelay)
-> KeepAliveDelay -> Parser KeepAliveDelay
forall a b. (a -> b) -> a -> b
$ KeepAliveDelay {Refined NonNegative Seconds
unKeepAliveDelay :: Refined NonNegative Seconds
unKeepAliveDelay :: Refined NonNegative Seconds
..}
instance ToJSON KeepAliveDelay where
toJSON :: KeepAliveDelay -> Value
toJSON KeepAliveDelay {Refined NonNegative Seconds
unKeepAliveDelay :: KeepAliveDelay -> Refined NonNegative Seconds
unKeepAliveDelay :: Refined NonNegative Seconds
..} =
[Pair] -> Value
J.object [Key
"keep_alive_delay" Key -> Refined NonNegative Seconds -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Refined NonNegative Seconds
unKeepAliveDelay]
newtype WSConnectionInitTimeout = WSConnectionInitTimeout {WSConnectionInitTimeout -> Refined NonNegative Seconds
unWSConnectionInitTimeout :: Refined NonNegative Seconds}
deriving newtype (Int -> WSConnectionInitTimeout -> ShowS
[WSConnectionInitTimeout] -> ShowS
WSConnectionInitTimeout -> String
(Int -> WSConnectionInitTimeout -> ShowS)
-> (WSConnectionInitTimeout -> String)
-> ([WSConnectionInitTimeout] -> ShowS)
-> Show WSConnectionInitTimeout
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WSConnectionInitTimeout -> ShowS
showsPrec :: Int -> WSConnectionInitTimeout -> ShowS
$cshow :: WSConnectionInitTimeout -> String
show :: WSConnectionInitTimeout -> String
$cshowList :: [WSConnectionInitTimeout] -> ShowS
showList :: [WSConnectionInitTimeout] -> ShowS
Show, WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
(WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> Eq WSConnectionInitTimeout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
== :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
$c/= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
/= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
Eq, Eq WSConnectionInitTimeout
Eq WSConnectionInitTimeout
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Ordering)
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> (WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool)
-> (WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout)
-> (WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout)
-> Ord WSConnectionInitTimeout
WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
WSConnectionInitTimeout -> WSConnectionInitTimeout -> Ordering
WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Ordering
compare :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Ordering
$c< :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
< :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
$c<= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
<= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
$c> :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
> :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
$c>= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
>= :: WSConnectionInitTimeout -> WSConnectionInitTimeout -> Bool
$cmax :: WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout
max :: WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout
$cmin :: WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout
min :: WSConnectionInitTimeout
-> WSConnectionInitTimeout -> WSConnectionInitTimeout
Ord)
instance FromJSON WSConnectionInitTimeout where
parseJSON :: Value -> Parser WSConnectionInitTimeout
parseJSON = String
-> (Object -> Parser WSConnectionInitTimeout)
-> Value
-> Parser WSConnectionInitTimeout
forall a. String -> (Object -> Parser a) -> Value -> Parser a
J.withObject String
"WSConnectionInitTimeout" \Object
o -> do
Refined NonNegative Seconds
unWSConnectionInitTimeout <- Object
o Object -> Key -> Parser (Refined NonNegative Seconds)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"w_s_connection_init_timeout"
WSConnectionInitTimeout -> Parser WSConnectionInitTimeout
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WSConnectionInitTimeout -> Parser WSConnectionInitTimeout)
-> WSConnectionInitTimeout -> Parser WSConnectionInitTimeout
forall a b. (a -> b) -> a -> b
$ WSConnectionInitTimeout {Refined NonNegative Seconds
unWSConnectionInitTimeout :: Refined NonNegative Seconds
unWSConnectionInitTimeout :: Refined NonNegative Seconds
..}
instance ToJSON WSConnectionInitTimeout where
toJSON :: WSConnectionInitTimeout -> Value
toJSON WSConnectionInitTimeout {Refined NonNegative Seconds
unWSConnectionInitTimeout :: WSConnectionInitTimeout -> Refined NonNegative Seconds
unWSConnectionInitTimeout :: Refined NonNegative Seconds
..} =
[Pair] -> Value
J.object [Key
"w_s_connection_init_timeout" Key -> Refined NonNegative Seconds -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Refined NonNegative Seconds
unWSConnectionInitTimeout]
data ServeOptions impl = ServeOptions
{ forall impl. ServeOptions impl -> Port
soPort :: Port,
forall impl. ServeOptions impl -> HostPreference
soHost :: Warp.HostPreference,
forall impl. ServeOptions impl -> ConnParams
soConnParams :: Query.ConnParams,
forall impl. ServeOptions impl -> TxIsolation
soTxIso :: Query.TxIsolation,
forall impl. ServeOptions impl -> HashSet AdminSecretHash
soAdminSecret :: HashSet Auth.AdminSecretHash,
forall impl. ServeOptions impl -> Maybe AuthHook
soAuthHook :: Maybe Auth.AuthHook,
forall impl. ServeOptions impl -> [JWTConfig]
soJwtSecret :: [Auth.JWTConfig],
forall impl. ServeOptions impl -> Maybe RoleName
soUnAuthRole :: Maybe RoleName,
forall impl. ServeOptions impl -> CorsConfig
soCorsConfig :: Cors.CorsConfig,
forall impl. ServeOptions impl -> ConsoleStatus
soConsoleStatus :: ConsoleStatus,
forall impl. ServeOptions impl -> Maybe Text
soConsoleAssetsDir :: Maybe Text,
forall impl. ServeOptions impl -> Maybe Text
soConsoleSentryDsn :: Maybe Text,
forall impl. ServeOptions impl -> TelemetryStatus
soEnableTelemetry :: TelemetryStatus,
forall impl. ServeOptions impl -> StringifyNumbers
soStringifyNum :: Schema.Options.StringifyNumbers,
forall impl. ServeOptions impl -> DangerouslyCollapseBooleans
soDangerousBooleanCollapse :: Schema.Options.DangerouslyCollapseBooleans,
forall impl. ServeOptions impl -> HashSet API
soEnabledAPIs :: HashSet API,
forall impl. ServeOptions impl -> LiveQueriesOptions
soLiveQueryOpts :: Subscription.Options.LiveQueriesOptions,
forall impl. ServeOptions impl -> LiveQueriesOptions
soStreamingQueryOpts :: Subscription.Options.StreamQueriesOptions,
forall impl. ServeOptions impl -> AllowListStatus
soEnableAllowList :: AllowListStatus,
forall impl. ServeOptions impl -> HashSet (EngineLogType impl)
soEnabledLogTypes :: HashSet (Logging.EngineLogType impl),
forall impl. ServeOptions impl -> LogLevel
soLogLevel :: Logging.LogLevel,
forall impl. ServeOptions impl -> Refined Positive Int
soEventsHttpPoolSize :: Refined Positive Int,
forall impl. ServeOptions impl -> Refined NonNegative Milliseconds
soEventsFetchInterval :: Refined NonNegative Milliseconds,
forall impl. ServeOptions impl -> OptionalInterval
soAsyncActionsFetchInterval :: OptionalInterval,
forall impl. ServeOptions impl -> RemoteSchemaPermissions
soEnableRemoteSchemaPermissions :: Schema.Options.RemoteSchemaPermissions,
forall impl. ServeOptions impl -> ConnectionOptions
soConnectionOptions :: WebSockets.ConnectionOptions,
forall impl. ServeOptions impl -> KeepAliveDelay
soWebSocketKeepAlive :: KeepAliveDelay,
forall impl. ServeOptions impl -> InferFunctionPermissions
soInferFunctionPermissions :: Schema.Options.InferFunctionPermissions,
forall impl. ServeOptions impl -> MaintenanceMode ()
soEnableMaintenanceMode :: Server.Types.MaintenanceMode (),
forall impl. ServeOptions impl -> OptionalInterval
soSchemaPollInterval :: OptionalInterval,
forall impl. ServeOptions impl -> HashSet ExperimentalFeature
soExperimentalFeatures :: HashSet Server.Types.ExperimentalFeature,
forall impl. ServeOptions impl -> Refined NonNegative Int
soEventsFetchBatchSize :: Refined NonNegative Int,
forall impl. ServeOptions impl -> DevModeStatus
soDevMode :: DevModeStatus,
forall impl. ServeOptions impl -> AdminInternalErrorsStatus
soAdminInternalErrors :: AdminInternalErrorsStatus,
forall impl. ServeOptions impl -> Refined NonNegative Seconds
soGracefulShutdownTimeout :: Refined NonNegative Seconds,
forall impl. ServeOptions impl -> WSConnectionInitTimeout
soWebSocketConnectionInitTimeout :: WSConnectionInitTimeout,
forall impl. ServeOptions impl -> EventingMode
soEventingMode :: Server.Types.EventingMode,
forall impl. ServeOptions impl -> ReadOnlyMode
soReadOnlyMode :: Server.Types.ReadOnlyMode,
forall impl. ServeOptions impl -> MetadataQueryLoggingMode
soEnableMetadataQueryLogging :: Server.Logging.MetadataQueryLoggingMode,
forall impl. ServeOptions impl -> NamingCase
soDefaultNamingConvention :: NamingCase,
forall impl. ServeOptions impl -> ExtensionsSchema
soExtensionsSchema :: MonadTx.ExtensionsSchema,
forall impl. ServeOptions impl -> MetadataDefaults
soMetadataDefaults :: MetadataDefaults,
forall impl. ServeOptions impl -> ApolloFederationStatus
soApolloFederationStatus :: Server.Types.ApolloFederationStatus,
forall impl.
ServeOptions impl -> CloseWebsocketsOnMetadataChangeStatus
soCloseWebsocketsOnMetadataChangeStatus :: Server.Types.CloseWebsocketsOnMetadataChangeStatus,
:: Int
}
data ResponseInternalErrorsConfig
= InternalErrorsAllRequests
| InternalErrorsAdminOnly
| InternalErrorsDisabled
deriving (Int -> ResponseInternalErrorsConfig -> ShowS
[ResponseInternalErrorsConfig] -> ShowS
ResponseInternalErrorsConfig -> String
(Int -> ResponseInternalErrorsConfig -> ShowS)
-> (ResponseInternalErrorsConfig -> String)
-> ([ResponseInternalErrorsConfig] -> ShowS)
-> Show ResponseInternalErrorsConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResponseInternalErrorsConfig -> ShowS
showsPrec :: Int -> ResponseInternalErrorsConfig -> ShowS
$cshow :: ResponseInternalErrorsConfig -> String
show :: ResponseInternalErrorsConfig -> String
$cshowList :: [ResponseInternalErrorsConfig] -> ShowS
showList :: [ResponseInternalErrorsConfig] -> ShowS
Show, ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool
(ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool)
-> (ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool)
-> Eq ResponseInternalErrorsConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool
== :: ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool
$c/= :: ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool
/= :: ResponseInternalErrorsConfig
-> ResponseInternalErrorsConfig -> Bool
Eq)
shouldIncludeInternal :: RoleName -> ResponseInternalErrorsConfig -> Bool
shouldIncludeInternal :: RoleName -> ResponseInternalErrorsConfig -> Bool
shouldIncludeInternal RoleName
role = \case
ResponseInternalErrorsConfig
InternalErrorsAllRequests -> Bool
True
ResponseInternalErrorsConfig
InternalErrorsAdminOnly -> RoleName
role RoleName -> RoleName -> Bool
forall a. Eq a => a -> a -> Bool
== RoleName
adminRoleName
ResponseInternalErrorsConfig
InternalErrorsDisabled -> Bool
False
data DowngradeOptions = DowngradeOptions
{ DowngradeOptions -> Text
dgoTargetVersion :: Text,
DowngradeOptions -> Bool
dgoDryRun :: Bool
}
deriving (Int -> DowngradeOptions -> ShowS
[DowngradeOptions] -> ShowS
DowngradeOptions -> String
(Int -> DowngradeOptions -> ShowS)
-> (DowngradeOptions -> String)
-> ([DowngradeOptions] -> ShowS)
-> Show DowngradeOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DowngradeOptions -> ShowS
showsPrec :: Int -> DowngradeOptions -> ShowS
$cshow :: DowngradeOptions -> String
show :: DowngradeOptions -> String
$cshowList :: [DowngradeOptions] -> ShowS
showList :: [DowngradeOptions] -> ShowS
Show, DowngradeOptions -> DowngradeOptions -> Bool
(DowngradeOptions -> DowngradeOptions -> Bool)
-> (DowngradeOptions -> DowngradeOptions -> Bool)
-> Eq DowngradeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DowngradeOptions -> DowngradeOptions -> Bool
== :: DowngradeOptions -> DowngradeOptions -> Bool
$c/= :: DowngradeOptions -> DowngradeOptions -> Bool
/= :: DowngradeOptions -> DowngradeOptions -> Bool
Eq)