{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
module WikiMusic.SSR.Model.Config
( AppConfig (..),
ServantConfig (..),
CorsConfig (..),
CookieConfig (..),
WebFrontendConfig (..),
appConfigCodec,
)
where
import Optics
import Relude
import Toml
data ServantConfig = ServantConfig
{ ServantConfig -> Int
port :: Int,
ServantConfig -> Text
host :: Text
}
deriving ((forall x. ServantConfig -> Rep ServantConfig x)
-> (forall x. Rep ServantConfig x -> ServantConfig)
-> Generic ServantConfig
forall x. Rep ServantConfig x -> ServantConfig
forall x. ServantConfig -> Rep ServantConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServantConfig -> Rep ServantConfig x
from :: forall x. ServantConfig -> Rep ServantConfig x
$cto :: forall x. Rep ServantConfig x -> ServantConfig
to :: forall x. Rep ServantConfig x -> ServantConfig
Generic, ServantConfig -> ServantConfig -> Bool
(ServantConfig -> ServantConfig -> Bool)
-> (ServantConfig -> ServantConfig -> Bool) -> Eq ServantConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServantConfig -> ServantConfig -> Bool
== :: ServantConfig -> ServantConfig -> Bool
$c/= :: ServantConfig -> ServantConfig -> Bool
/= :: ServantConfig -> ServantConfig -> Bool
Eq, Int -> ServantConfig -> ShowS
[ServantConfig] -> ShowS
ServantConfig -> String
(Int -> ServantConfig -> ShowS)
-> (ServantConfig -> String)
-> ([ServantConfig] -> ShowS)
-> Show ServantConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServantConfig -> ShowS
showsPrec :: Int -> ServantConfig -> ShowS
$cshow :: ServantConfig -> String
show :: ServantConfig -> String
$cshowList :: [ServantConfig] -> ShowS
showList :: [ServantConfig] -> ShowS
Show)
servantConfigCodec :: TomlCodec ServantConfig
servantConfigCodec :: TomlCodec ServantConfig
servantConfigCodec =
Int -> Text -> ServantConfig
ServantConfig
(Int -> Text -> ServantConfig)
-> Codec ServantConfig Int
-> Codec ServantConfig (Text -> ServantConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Int
Toml.int Key
"port"
TomlCodec Int -> (ServantConfig -> Int) -> Codec ServantConfig Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (ServantConfig -> Optic' A_Lens NoIx ServantConfig Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ServantConfig Int
#port)
Codec ServantConfig (Text -> ServantConfig)
-> Codec ServantConfig Text -> TomlCodec ServantConfig
forall a b.
Codec ServantConfig (a -> b)
-> Codec ServantConfig a -> Codec ServantConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"host"
TomlCodec Text
-> (ServantConfig -> Text) -> Codec ServantConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (ServantConfig -> Optic' A_Lens NoIx ServantConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx ServantConfig Text
#host)
data CorsConfig = CorsConfig
{ CorsConfig -> [Text]
origins :: [Text],
CorsConfig -> [Text]
methods :: [Text],
:: [Text]
}
deriving ((forall x. CorsConfig -> Rep CorsConfig x)
-> (forall x. Rep CorsConfig x -> CorsConfig) -> Generic CorsConfig
forall x. Rep CorsConfig x -> CorsConfig
forall x. CorsConfig -> Rep CorsConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CorsConfig -> Rep CorsConfig x
from :: forall x. CorsConfig -> Rep CorsConfig x
$cto :: forall x. Rep CorsConfig x -> CorsConfig
to :: forall x. Rep CorsConfig x -> CorsConfig
Generic, CorsConfig -> CorsConfig -> Bool
(CorsConfig -> CorsConfig -> Bool)
-> (CorsConfig -> CorsConfig -> Bool) -> Eq CorsConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CorsConfig -> CorsConfig -> Bool
== :: CorsConfig -> CorsConfig -> Bool
$c/= :: CorsConfig -> CorsConfig -> Bool
/= :: CorsConfig -> CorsConfig -> Bool
Eq, Int -> CorsConfig -> ShowS
[CorsConfig] -> ShowS
CorsConfig -> String
(Int -> CorsConfig -> ShowS)
-> (CorsConfig -> String)
-> ([CorsConfig] -> ShowS)
-> Show CorsConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CorsConfig -> ShowS
showsPrec :: Int -> CorsConfig -> ShowS
$cshow :: CorsConfig -> String
show :: CorsConfig -> String
$cshowList :: [CorsConfig] -> ShowS
showList :: [CorsConfig] -> ShowS
Show)
corsConfigCodec :: TomlCodec CorsConfig
corsConfigCodec :: TomlCodec CorsConfig
corsConfigCodec =
[Text] -> [Text] -> [Text] -> CorsConfig
CorsConfig
([Text] -> [Text] -> [Text] -> CorsConfig)
-> Codec CorsConfig [Text]
-> Codec CorsConfig ([Text] -> [Text] -> CorsConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TomlBiMap Text AnyValue -> Key -> TomlCodec [Text]
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec [a]
Toml.arrayOf TomlBiMap Text AnyValue
Toml._Text Key
"origins"
TomlCodec [Text]
-> (CorsConfig -> [Text]) -> Codec CorsConfig [Text]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CorsConfig -> Optic' A_Lens NoIx CorsConfig [Text] -> [Text]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CorsConfig [Text]
#origins)
Codec CorsConfig ([Text] -> [Text] -> CorsConfig)
-> Codec CorsConfig [Text]
-> Codec CorsConfig ([Text] -> CorsConfig)
forall a b.
Codec CorsConfig (a -> b)
-> Codec CorsConfig a -> Codec CorsConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlBiMap Text AnyValue -> Key -> TomlCodec [Text]
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec [a]
Toml.arrayOf TomlBiMap Text AnyValue
Toml._Text Key
"methods"
TomlCodec [Text]
-> (CorsConfig -> [Text]) -> Codec CorsConfig [Text]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CorsConfig -> Optic' A_Lens NoIx CorsConfig [Text] -> [Text]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CorsConfig [Text]
#methods)
Codec CorsConfig ([Text] -> CorsConfig)
-> Codec CorsConfig [Text] -> TomlCodec CorsConfig
forall a b.
Codec CorsConfig (a -> b)
-> Codec CorsConfig a -> Codec CorsConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlBiMap Text AnyValue -> Key -> TomlCodec [Text]
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec [a]
Toml.arrayOf TomlBiMap Text AnyValue
Toml._Text Key
"request-headers"
TomlCodec [Text]
-> (CorsConfig -> [Text]) -> Codec CorsConfig [Text]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CorsConfig -> Optic' A_Lens NoIx CorsConfig [Text] -> [Text]
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CorsConfig [Text]
#requestHeaders)
data CookieConfig = CookieConfig
{ CookieConfig -> Int
maxAge :: Int,
CookieConfig -> Text
path :: Text,
CookieConfig -> Text
domain :: Text,
CookieConfig -> Bool
secure :: Bool,
CookieConfig -> Text
sameSite :: Text
}
deriving ((forall x. CookieConfig -> Rep CookieConfig x)
-> (forall x. Rep CookieConfig x -> CookieConfig)
-> Generic CookieConfig
forall x. Rep CookieConfig x -> CookieConfig
forall x. CookieConfig -> Rep CookieConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CookieConfig -> Rep CookieConfig x
from :: forall x. CookieConfig -> Rep CookieConfig x
$cto :: forall x. Rep CookieConfig x -> CookieConfig
to :: forall x. Rep CookieConfig x -> CookieConfig
Generic, CookieConfig -> CookieConfig -> Bool
(CookieConfig -> CookieConfig -> Bool)
-> (CookieConfig -> CookieConfig -> Bool) -> Eq CookieConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CookieConfig -> CookieConfig -> Bool
== :: CookieConfig -> CookieConfig -> Bool
$c/= :: CookieConfig -> CookieConfig -> Bool
/= :: CookieConfig -> CookieConfig -> Bool
Eq, Int -> CookieConfig -> ShowS
[CookieConfig] -> ShowS
CookieConfig -> String
(Int -> CookieConfig -> ShowS)
-> (CookieConfig -> String)
-> ([CookieConfig] -> ShowS)
-> Show CookieConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CookieConfig -> ShowS
showsPrec :: Int -> CookieConfig -> ShowS
$cshow :: CookieConfig -> String
show :: CookieConfig -> String
$cshowList :: [CookieConfig] -> ShowS
showList :: [CookieConfig] -> ShowS
Show)
cookieConfigCodec :: TomlCodec CookieConfig
cookieConfigCodec :: TomlCodec CookieConfig
cookieConfigCodec =
Int -> Text -> Text -> Bool -> Text -> CookieConfig
CookieConfig
(Int -> Text -> Text -> Bool -> Text -> CookieConfig)
-> Codec CookieConfig Int
-> Codec
CookieConfig (Text -> Text -> Bool -> Text -> CookieConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Int
Toml.int Key
"max-age"
TomlCodec Int -> (CookieConfig -> Int) -> Codec CookieConfig Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CookieConfig -> Optic' A_Lens NoIx CookieConfig Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CookieConfig Int
#maxAge)
Codec CookieConfig (Text -> Text -> Bool -> Text -> CookieConfig)
-> Codec CookieConfig Text
-> Codec CookieConfig (Text -> Bool -> Text -> CookieConfig)
forall a b.
Codec CookieConfig (a -> b)
-> Codec CookieConfig a -> Codec CookieConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"path"
TomlCodec Text -> (CookieConfig -> Text) -> Codec CookieConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CookieConfig -> Optic' A_Lens NoIx CookieConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CookieConfig Text
#path)
Codec CookieConfig (Text -> Bool -> Text -> CookieConfig)
-> Codec CookieConfig Text
-> Codec CookieConfig (Bool -> Text -> CookieConfig)
forall a b.
Codec CookieConfig (a -> b)
-> Codec CookieConfig a -> Codec CookieConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"domain"
TomlCodec Text -> (CookieConfig -> Text) -> Codec CookieConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CookieConfig -> Optic' A_Lens NoIx CookieConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CookieConfig Text
#domain)
Codec CookieConfig (Bool -> Text -> CookieConfig)
-> Codec CookieConfig Bool
-> Codec CookieConfig (Text -> CookieConfig)
forall a b.
Codec CookieConfig (a -> b)
-> Codec CookieConfig a -> Codec CookieConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Bool
Toml.bool Key
"secure"
TomlCodec Bool -> (CookieConfig -> Bool) -> Codec CookieConfig Bool
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CookieConfig -> Optic' A_Lens NoIx CookieConfig Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CookieConfig Bool
#secure)
Codec CookieConfig (Text -> CookieConfig)
-> Codec CookieConfig Text -> TomlCodec CookieConfig
forall a b.
Codec CookieConfig (a -> b)
-> Codec CookieConfig a -> Codec CookieConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"same-site"
TomlCodec Text -> (CookieConfig -> Text) -> Codec CookieConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (CookieConfig -> Optic' A_Lens NoIx CookieConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx CookieConfig Text
#sameSite)
newtype DevConfig = DevConfig
{ DevConfig -> Text
reportedVersion :: Text
}
deriving ((forall x. DevConfig -> Rep DevConfig x)
-> (forall x. Rep DevConfig x -> DevConfig) -> Generic DevConfig
forall x. Rep DevConfig x -> DevConfig
forall x. DevConfig -> Rep DevConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DevConfig -> Rep DevConfig x
from :: forall x. DevConfig -> Rep DevConfig x
$cto :: forall x. Rep DevConfig x -> DevConfig
to :: forall x. Rep DevConfig x -> DevConfig
Generic, DevConfig -> DevConfig -> Bool
(DevConfig -> DevConfig -> Bool)
-> (DevConfig -> DevConfig -> Bool) -> Eq DevConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DevConfig -> DevConfig -> Bool
== :: DevConfig -> DevConfig -> Bool
$c/= :: DevConfig -> DevConfig -> Bool
/= :: DevConfig -> DevConfig -> Bool
Eq, Int -> DevConfig -> ShowS
[DevConfig] -> ShowS
DevConfig -> String
(Int -> DevConfig -> ShowS)
-> (DevConfig -> String)
-> ([DevConfig] -> ShowS)
-> Show DevConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DevConfig -> ShowS
showsPrec :: Int -> DevConfig -> ShowS
$cshow :: DevConfig -> String
show :: DevConfig -> String
$cshowList :: [DevConfig] -> ShowS
showList :: [DevConfig] -> ShowS
Show)
devCodec :: TomlCodec DevConfig
devCodec :: TomlCodec DevConfig
devCodec = Text -> DevConfig
DevConfig (Text -> DevConfig) -> Codec DevConfig Text -> TomlCodec DevConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Text
Toml.text Key
"reported-version" TomlCodec Text -> (DevConfig -> Text) -> Codec DevConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (DevConfig -> Optic' A_Lens NoIx DevConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx DevConfig Text
#reportedVersion)
newtype WebFrontendConfig = WebFrontendConfig
{ WebFrontendConfig -> Text
baseUrl :: Text
}
deriving ((forall x. WebFrontendConfig -> Rep WebFrontendConfig x)
-> (forall x. Rep WebFrontendConfig x -> WebFrontendConfig)
-> Generic WebFrontendConfig
forall x. Rep WebFrontendConfig x -> WebFrontendConfig
forall x. WebFrontendConfig -> Rep WebFrontendConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. WebFrontendConfig -> Rep WebFrontendConfig x
from :: forall x. WebFrontendConfig -> Rep WebFrontendConfig x
$cto :: forall x. Rep WebFrontendConfig x -> WebFrontendConfig
to :: forall x. Rep WebFrontendConfig x -> WebFrontendConfig
Generic, WebFrontendConfig -> WebFrontendConfig -> Bool
(WebFrontendConfig -> WebFrontendConfig -> Bool)
-> (WebFrontendConfig -> WebFrontendConfig -> Bool)
-> Eq WebFrontendConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: WebFrontendConfig -> WebFrontendConfig -> Bool
== :: WebFrontendConfig -> WebFrontendConfig -> Bool
$c/= :: WebFrontendConfig -> WebFrontendConfig -> Bool
/= :: WebFrontendConfig -> WebFrontendConfig -> Bool
Eq, Int -> WebFrontendConfig -> ShowS
[WebFrontendConfig] -> ShowS
WebFrontendConfig -> String
(Int -> WebFrontendConfig -> ShowS)
-> (WebFrontendConfig -> String)
-> ([WebFrontendConfig] -> ShowS)
-> Show WebFrontendConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> WebFrontendConfig -> ShowS
showsPrec :: Int -> WebFrontendConfig -> ShowS
$cshow :: WebFrontendConfig -> String
show :: WebFrontendConfig -> String
$cshowList :: [WebFrontendConfig] -> ShowS
showList :: [WebFrontendConfig] -> ShowS
Show)
webFrontendConfigCodec :: TomlCodec WebFrontendConfig
webFrontendConfigCodec :: TomlCodec WebFrontendConfig
webFrontendConfigCodec =
Text -> WebFrontendConfig
WebFrontendConfig
(Text -> WebFrontendConfig)
-> Codec WebFrontendConfig Text -> TomlCodec WebFrontendConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Text
Toml.text Key
"base-url"
TomlCodec Text
-> (WebFrontendConfig -> Text) -> Codec WebFrontendConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (WebFrontendConfig
-> Optic' A_Lens NoIx WebFrontendConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx WebFrontendConfig Text
#baseUrl)
data AppConfig = AppConfig
{ AppConfig -> ServantConfig
servant :: ServantConfig,
AppConfig -> CorsConfig
cors :: CorsConfig,
AppConfig -> CookieConfig
cookie :: CookieConfig,
AppConfig -> WebFrontendConfig
webFrontend :: WebFrontendConfig,
AppConfig -> DevConfig
dev :: DevConfig
}
deriving ((forall x. AppConfig -> Rep AppConfig x)
-> (forall x. Rep AppConfig x -> AppConfig) -> Generic AppConfig
forall x. Rep AppConfig x -> AppConfig
forall x. AppConfig -> Rep AppConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AppConfig -> Rep AppConfig x
from :: forall x. AppConfig -> Rep AppConfig x
$cto :: forall x. Rep AppConfig x -> AppConfig
to :: forall x. Rep AppConfig x -> AppConfig
Generic, AppConfig -> AppConfig -> Bool
(AppConfig -> AppConfig -> Bool)
-> (AppConfig -> AppConfig -> Bool) -> Eq AppConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AppConfig -> AppConfig -> Bool
== :: AppConfig -> AppConfig -> Bool
$c/= :: AppConfig -> AppConfig -> Bool
/= :: AppConfig -> AppConfig -> Bool
Eq, Int -> AppConfig -> ShowS
[AppConfig] -> ShowS
AppConfig -> String
(Int -> AppConfig -> ShowS)
-> (AppConfig -> String)
-> ([AppConfig] -> ShowS)
-> Show AppConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AppConfig -> ShowS
showsPrec :: Int -> AppConfig -> ShowS
$cshow :: AppConfig -> String
show :: AppConfig -> String
$cshowList :: [AppConfig] -> ShowS
showList :: [AppConfig] -> ShowS
Show)
appConfigCodec :: TomlCodec AppConfig
appConfigCodec :: TomlCodec AppConfig
appConfigCodec =
ServantConfig
-> CorsConfig
-> CookieConfig
-> WebFrontendConfig
-> DevConfig
-> AppConfig
AppConfig
(ServantConfig
-> CorsConfig
-> CookieConfig
-> WebFrontendConfig
-> DevConfig
-> AppConfig)
-> Codec AppConfig ServantConfig
-> Codec
AppConfig
(CorsConfig
-> CookieConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TomlCodec ServantConfig -> Key -> TomlCodec ServantConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec ServantConfig
servantConfigCodec Key
"servant"
TomlCodec ServantConfig
-> (AppConfig -> ServantConfig) -> Codec AppConfig ServantConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig
-> Optic' A_Lens NoIx AppConfig ServantConfig -> ServantConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig ServantConfig
#servant)
Codec
AppConfig
(CorsConfig
-> CookieConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
-> Codec AppConfig CorsConfig
-> Codec
AppConfig
(CookieConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
forall a b.
Codec AppConfig (a -> b) -> Codec AppConfig a -> Codec AppConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec CorsConfig -> Key -> TomlCodec CorsConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec CorsConfig
corsConfigCodec Key
"cors"
TomlCodec CorsConfig
-> (AppConfig -> CorsConfig) -> Codec AppConfig CorsConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig -> Optic' A_Lens NoIx AppConfig CorsConfig -> CorsConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig CorsConfig
#cors)
Codec
AppConfig
(CookieConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
-> Codec AppConfig CookieConfig
-> Codec AppConfig (WebFrontendConfig -> DevConfig -> AppConfig)
forall a b.
Codec AppConfig (a -> b) -> Codec AppConfig a -> Codec AppConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec CookieConfig -> Key -> TomlCodec CookieConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec CookieConfig
cookieConfigCodec Key
"cookie"
TomlCodec CookieConfig
-> (AppConfig -> CookieConfig) -> Codec AppConfig CookieConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig
-> Optic' A_Lens NoIx AppConfig CookieConfig -> CookieConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig CookieConfig
#cookie)
Codec AppConfig (WebFrontendConfig -> DevConfig -> AppConfig)
-> Codec AppConfig WebFrontendConfig
-> Codec AppConfig (DevConfig -> AppConfig)
forall a b.
Codec AppConfig (a -> b) -> Codec AppConfig a -> Codec AppConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec WebFrontendConfig -> Key -> TomlCodec WebFrontendConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec WebFrontendConfig
webFrontendConfigCodec Key
"web-frontend"
TomlCodec WebFrontendConfig
-> (AppConfig -> WebFrontendConfig)
-> Codec AppConfig WebFrontendConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig
-> Optic' A_Lens NoIx AppConfig WebFrontendConfig
-> WebFrontendConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig WebFrontendConfig
#webFrontend)
Codec AppConfig (DevConfig -> AppConfig)
-> Codec AppConfig DevConfig -> TomlCodec AppConfig
forall a b.
Codec AppConfig (a -> b) -> Codec AppConfig a -> Codec AppConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec DevConfig -> Key -> TomlCodec DevConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec DevConfig
devCodec Key
"dev"
TomlCodec DevConfig
-> (AppConfig -> DevConfig) -> Codec AppConfig DevConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig -> Optic' A_Lens NoIx AppConfig DevConfig -> DevConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig DevConfig
#dev)
makeFieldLabelsNoPrefix ''AppConfig
makeFieldLabelsNoPrefix ''ServantConfig
makeFieldLabelsNoPrefix ''CorsConfig
makeFieldLabelsNoPrefix ''CookieConfig
makeFieldLabelsNoPrefix ''WebFrontendConfig
makeFieldLabelsNoPrefix ''DevConfig