module Ribosome.Host.Data.HostConfig where
import Log (Severity (Crit, Info))
import Path (Abs, File, Path)
data LogConfig =
LogConfig {
LogConfig -> Maybe (Path Abs File)
logFile :: Maybe (Path Abs File),
LogConfig -> Severity
logLevelEcho :: Severity,
LogConfig -> Severity
logLevelStderr :: Severity,
LogConfig -> Severity
logLevelFile :: Severity,
LogConfig -> Bool
dataLogConc :: Bool
}
deriving stock (LogConfig -> LogConfig -> Bool
(LogConfig -> LogConfig -> Bool)
-> (LogConfig -> LogConfig -> Bool) -> Eq LogConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogConfig -> LogConfig -> Bool
$c/= :: LogConfig -> LogConfig -> Bool
== :: LogConfig -> LogConfig -> Bool
$c== :: LogConfig -> LogConfig -> Bool
Eq, Int -> LogConfig -> ShowS
[LogConfig] -> ShowS
LogConfig -> String
(Int -> LogConfig -> ShowS)
-> (LogConfig -> String)
-> ([LogConfig] -> ShowS)
-> Show LogConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogConfig] -> ShowS
$cshowList :: [LogConfig] -> ShowS
show :: LogConfig -> String
$cshow :: LogConfig -> String
showsPrec :: Int -> LogConfig -> ShowS
$cshowsPrec :: Int -> LogConfig -> ShowS
Show, (forall x. LogConfig -> Rep LogConfig x)
-> (forall x. Rep LogConfig x -> LogConfig) -> Generic LogConfig
forall x. Rep LogConfig x -> LogConfig
forall x. LogConfig -> Rep LogConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogConfig x -> LogConfig
$cfrom :: forall x. LogConfig -> Rep LogConfig x
Generic)
instance Default LogConfig where
def :: LogConfig
def =
Maybe (Path Abs File)
-> Severity -> Severity -> Severity -> Bool -> LogConfig
LogConfig Maybe (Path Abs File)
forall a. Maybe a
Nothing Severity
Info Severity
Crit Severity
Info Bool
True
newtype HostConfig =
HostConfig {
HostConfig -> LogConfig
hostLog :: LogConfig
}
deriving stock (HostConfig -> HostConfig -> Bool
(HostConfig -> HostConfig -> Bool)
-> (HostConfig -> HostConfig -> Bool) -> Eq HostConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HostConfig -> HostConfig -> Bool
$c/= :: HostConfig -> HostConfig -> Bool
== :: HostConfig -> HostConfig -> Bool
$c== :: HostConfig -> HostConfig -> Bool
Eq, Int -> HostConfig -> ShowS
[HostConfig] -> ShowS
HostConfig -> String
(Int -> HostConfig -> ShowS)
-> (HostConfig -> String)
-> ([HostConfig] -> ShowS)
-> Show HostConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HostConfig] -> ShowS
$cshowList :: [HostConfig] -> ShowS
show :: HostConfig -> String
$cshow :: HostConfig -> String
showsPrec :: Int -> HostConfig -> ShowS
$cshowsPrec :: Int -> HostConfig -> ShowS
Show, (forall x. HostConfig -> Rep HostConfig x)
-> (forall x. Rep HostConfig x -> HostConfig) -> Generic HostConfig
forall x. Rep HostConfig x -> HostConfig
forall x. HostConfig -> Rep HostConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HostConfig x -> HostConfig
$cfrom :: forall x. HostConfig -> Rep HostConfig x
Generic)
instance Default HostConfig where
def :: HostConfig
def =
LogConfig -> HostConfig
HostConfig LogConfig
forall a. Default a => a
def
setStderr :: Severity -> HostConfig -> HostConfig
setStderr :: Severity -> HostConfig -> HostConfig
setStderr Severity
l HostConfig
c =
HostConfig
c { $sel:hostLog:HostConfig :: LogConfig
hostLog = (HostConfig -> LogConfig
hostLog HostConfig
c) { $sel:logLevelStderr:LogConfig :: Severity
logLevelStderr = Severity
l } }