{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoFieldSelectors #-}
module WikiMusic.Model.Config where
import Optics
import Relude
import Toml
data SqliteConfig = SqliteConfig
{ SqliteConfig -> Text
path :: Text,
SqliteConfig -> Bool
runMigrations :: Bool
}
deriving ((forall x. SqliteConfig -> Rep SqliteConfig x)
-> (forall x. Rep SqliteConfig x -> SqliteConfig)
-> Generic SqliteConfig
forall x. Rep SqliteConfig x -> SqliteConfig
forall x. SqliteConfig -> Rep SqliteConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SqliteConfig -> Rep SqliteConfig x
from :: forall x. SqliteConfig -> Rep SqliteConfig x
$cto :: forall x. Rep SqliteConfig x -> SqliteConfig
to :: forall x. Rep SqliteConfig x -> SqliteConfig
Generic, SqliteConfig -> SqliteConfig -> Bool
(SqliteConfig -> SqliteConfig -> Bool)
-> (SqliteConfig -> SqliteConfig -> Bool) -> Eq SqliteConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SqliteConfig -> SqliteConfig -> Bool
== :: SqliteConfig -> SqliteConfig -> Bool
$c/= :: SqliteConfig -> SqliteConfig -> Bool
/= :: SqliteConfig -> SqliteConfig -> Bool
Eq, Int -> SqliteConfig -> ShowS
[SqliteConfig] -> ShowS
SqliteConfig -> String
(Int -> SqliteConfig -> ShowS)
-> (SqliteConfig -> String)
-> ([SqliteConfig] -> ShowS)
-> Show SqliteConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SqliteConfig -> ShowS
showsPrec :: Int -> SqliteConfig -> ShowS
$cshow :: SqliteConfig -> String
show :: SqliteConfig -> String
$cshowList :: [SqliteConfig] -> ShowS
showList :: [SqliteConfig] -> ShowS
Show)
sqliteConfigCodec :: TomlCodec SqliteConfig
sqliteConfigCodec :: TomlCodec SqliteConfig
sqliteConfigCodec =
Text -> Bool -> SqliteConfig
SqliteConfig
(Text -> Bool -> SqliteConfig)
-> Codec SqliteConfig Text
-> Codec SqliteConfig (Bool -> SqliteConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Text
Toml.text Key
"path"
TomlCodec Text -> (SqliteConfig -> Text) -> Codec SqliteConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (SqliteConfig -> Optic' A_Lens NoIx SqliteConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SqliteConfig Text
#path)
Codec SqliteConfig (Bool -> SqliteConfig)
-> Codec SqliteConfig Bool -> TomlCodec SqliteConfig
forall a b.
Codec SqliteConfig (a -> b)
-> Codec SqliteConfig a -> Codec SqliteConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Bool
Toml.bool Key
"run-migrations"
TomlCodec Bool -> (SqliteConfig -> Bool) -> Codec SqliteConfig Bool
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (SqliteConfig -> Optic' A_Lens NoIx SqliteConfig Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SqliteConfig Bool
#runMigrations)
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 MailConfig = MailConfig
{ MailConfig -> Int
sendTimeoutSeconds :: Int,
MailConfig -> Text
host :: Text,
MailConfig -> Text
userFile :: Text,
MailConfig -> Maybe Text
user :: Maybe Text,
MailConfig -> Text
passwordFile :: Text,
MailConfig -> Maybe Text
password :: Maybe Text,
MailConfig -> Text
senderName :: Text,
MailConfig -> Text
senderMail :: Text
}
deriving ((forall x. MailConfig -> Rep MailConfig x)
-> (forall x. Rep MailConfig x -> MailConfig) -> Generic MailConfig
forall x. Rep MailConfig x -> MailConfig
forall x. MailConfig -> Rep MailConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MailConfig -> Rep MailConfig x
from :: forall x. MailConfig -> Rep MailConfig x
$cto :: forall x. Rep MailConfig x -> MailConfig
to :: forall x. Rep MailConfig x -> MailConfig
Generic, MailConfig -> MailConfig -> Bool
(MailConfig -> MailConfig -> Bool)
-> (MailConfig -> MailConfig -> Bool) -> Eq MailConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MailConfig -> MailConfig -> Bool
== :: MailConfig -> MailConfig -> Bool
$c/= :: MailConfig -> MailConfig -> Bool
/= :: MailConfig -> MailConfig -> Bool
Eq, Int -> MailConfig -> ShowS
[MailConfig] -> ShowS
MailConfig -> String
(Int -> MailConfig -> ShowS)
-> (MailConfig -> String)
-> ([MailConfig] -> ShowS)
-> Show MailConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MailConfig -> ShowS
showsPrec :: Int -> MailConfig -> ShowS
$cshow :: MailConfig -> String
show :: MailConfig -> String
$cshowList :: [MailConfig] -> ShowS
showList :: [MailConfig] -> ShowS
Show)
mailConfigCodec :: TomlCodec MailConfig
mailConfigCodec :: TomlCodec MailConfig
mailConfigCodec =
Int
-> Text
-> Text
-> Maybe Text
-> Text
-> Maybe Text
-> Text
-> Text
-> MailConfig
MailConfig
(Int
-> Text
-> Text
-> Maybe Text
-> Text
-> Maybe Text
-> Text
-> Text
-> MailConfig)
-> Codec MailConfig Int
-> Codec
MailConfig
(Text
-> Text
-> Maybe Text
-> Text
-> Maybe Text
-> Text
-> Text
-> MailConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Int
Toml.int Key
"send-timeout-seconds"
TomlCodec Int -> (MailConfig -> Int) -> Codec MailConfig Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Int -> Int
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Int
#sendTimeoutSeconds)
Codec
MailConfig
(Text
-> Text
-> Maybe Text
-> Text
-> Maybe Text
-> Text
-> Text
-> MailConfig)
-> Codec MailConfig Text
-> Codec
MailConfig
(Text
-> Maybe Text -> Text -> Maybe Text -> Text -> Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"host"
TomlCodec Text -> (MailConfig -> Text) -> Codec MailConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Text
#host)
Codec
MailConfig
(Text
-> Maybe Text -> Text -> Maybe Text -> Text -> Text -> MailConfig)
-> Codec MailConfig Text
-> Codec
MailConfig
(Maybe Text -> Text -> Maybe Text -> Text -> Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"user-file"
TomlCodec Text -> (MailConfig -> Text) -> Codec MailConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Text
#userFile)
Codec
MailConfig
(Maybe Text -> Text -> Maybe Text -> Text -> Text -> MailConfig)
-> Codec MailConfig (Maybe Text)
-> Codec
MailConfig (Text -> Maybe Text -> Text -> Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text Key
"user")
TomlCodec (Maybe Text)
-> (MailConfig -> Maybe Text) -> Codec MailConfig (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig
-> Optic' A_Lens NoIx MailConfig (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig (Maybe Text)
#user)
Codec MailConfig (Text -> Maybe Text -> Text -> Text -> MailConfig)
-> Codec MailConfig Text
-> Codec MailConfig (Maybe Text -> Text -> Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"password-file"
TomlCodec Text -> (MailConfig -> Text) -> Codec MailConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Text
#passwordFile)
Codec MailConfig (Maybe Text -> Text -> Text -> MailConfig)
-> Codec MailConfig (Maybe Text)
-> Codec MailConfig (Text -> Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text Key
"password")
TomlCodec (Maybe Text)
-> (MailConfig -> Maybe Text) -> Codec MailConfig (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig
-> Optic' A_Lens NoIx MailConfig (Maybe Text) -> Maybe Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig (Maybe Text)
#password)
Codec MailConfig (Text -> Text -> MailConfig)
-> Codec MailConfig Text -> Codec MailConfig (Text -> MailConfig)
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"sender-name"
TomlCodec Text -> (MailConfig -> Text) -> Codec MailConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Text
#senderName)
Codec MailConfig (Text -> MailConfig)
-> Codec MailConfig Text -> TomlCodec MailConfig
forall a b.
Codec MailConfig (a -> b)
-> Codec MailConfig a -> Codec MailConfig b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Key -> TomlCodec Text
Toml.text Key
"sender-mail"
TomlCodec Text -> (MailConfig -> Text) -> Codec MailConfig Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (MailConfig -> Optic' A_Lens NoIx MailConfig Text -> Text
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx MailConfig Text
#senderMail)
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)
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)
data AppConfig = AppConfig
{ AppConfig -> ServantConfig
servant :: ServantConfig,
AppConfig -> SqliteConfig
sqlite :: SqliteConfig,
AppConfig -> CorsConfig
cors :: CorsConfig,
AppConfig -> MailConfig
mail :: MailConfig,
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
-> SqliteConfig
-> CorsConfig
-> MailConfig
-> WebFrontendConfig
-> DevConfig
-> AppConfig
AppConfig
(ServantConfig
-> SqliteConfig
-> CorsConfig
-> MailConfig
-> WebFrontendConfig
-> DevConfig
-> AppConfig)
-> Codec AppConfig ServantConfig
-> Codec
AppConfig
(SqliteConfig
-> CorsConfig
-> MailConfig
-> 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
(SqliteConfig
-> CorsConfig
-> MailConfig
-> WebFrontendConfig
-> DevConfig
-> AppConfig)
-> Codec AppConfig SqliteConfig
-> Codec
AppConfig
(CorsConfig
-> MailConfig -> 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 SqliteConfig -> Key -> TomlCodec SqliteConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec SqliteConfig
sqliteConfigCodec Key
"sqlite"
TomlCodec SqliteConfig
-> (AppConfig -> SqliteConfig) -> Codec AppConfig SqliteConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig
-> Optic' A_Lens NoIx AppConfig SqliteConfig -> SqliteConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig SqliteConfig
#sqlite)
Codec
AppConfig
(CorsConfig
-> MailConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
-> Codec AppConfig CorsConfig
-> Codec
AppConfig
(MailConfig -> 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
(MailConfig -> WebFrontendConfig -> DevConfig -> AppConfig)
-> Codec AppConfig MailConfig
-> 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 MailConfig -> Key -> TomlCodec MailConfig
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec MailConfig
mailConfigCodec Key
"mail"
TomlCodec MailConfig
-> (AppConfig -> MailConfig) -> Codec AppConfig MailConfig
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= (AppConfig -> Optic' A_Lens NoIx AppConfig MailConfig -> MailConfig
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx AppConfig MailConfig
#mail)
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 ''SqliteConfig
makeFieldLabelsNoPrefix ''ServantConfig
makeFieldLabelsNoPrefix ''CorsConfig
makeFieldLabelsNoPrefix ''MailConfig
makeFieldLabelsNoPrefix ''WebFrontendConfig
makeFieldLabelsNoPrefix ''DevConfig