module Ribosome.Data.SettingError where
import Exon (exon)
import Log (Severity (Error))
import Ribosome.Host.Data.Report (Report (Report), Reportable (toReport))
import Ribosome.Host.Data.RpcError (RpcError, rpcError)
data SettingError =
Unset Text
|
Decode Text Text
|
UpdateFailed Text RpcError
deriving stock (SettingError -> SettingError -> Bool
(SettingError -> SettingError -> Bool)
-> (SettingError -> SettingError -> Bool) -> Eq SettingError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettingError -> SettingError -> Bool
$c/= :: SettingError -> SettingError -> Bool
== :: SettingError -> SettingError -> Bool
$c== :: SettingError -> SettingError -> Bool
Eq, Int -> SettingError -> ShowS
[SettingError] -> ShowS
SettingError -> String
(Int -> SettingError -> ShowS)
-> (SettingError -> String)
-> ([SettingError] -> ShowS)
-> Show SettingError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SettingError] -> ShowS
$cshowList :: [SettingError] -> ShowS
show :: SettingError -> String
$cshow :: SettingError -> String
showsPrec :: Int -> SettingError -> ShowS
$cshowsPrec :: Int -> SettingError -> ShowS
Show)
instance Reportable SettingError where
toReport :: SettingError -> Report
toReport = \case
Unset Text
key ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report [exon|Mandatory setting '#{key}' is unset|] [Item [Text]
"SettingError.Unset:", Text
Item [Text]
key] Severity
Error
Decode Text
key Text
msg ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report [exon|Setting '#{key}' has invalid value: #{msg}|] [Item [Text]
"SettingError.Decode:", Text
Item [Text]
key, Text
Item [Text]
msg] Severity
Error
UpdateFailed Text
key RpcError
err ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report [exon|Failed to update setting '#{key}': #{rpcError err}|] [Item [Text]
"SettingError.UpdateFailed:", Text
Item [Text]
key, RpcError -> Text
forall b a. (Show a, IsString b) => a -> b
show RpcError
err] Severity
Error