module Ribosome.Data.PersistError where
import Exon (exon)
import Polysemy.Log (Severity (Error))
import Ribosome.Data.PersistPathError (PersistPathError)
import Ribosome.Host.Data.Report (Report (Report), Reportable (toReport))
data PersistError =
Permission Text
|
Decode Text Text
|
Path PersistPathError
deriving stock (PersistError -> PersistError -> Bool
(PersistError -> PersistError -> Bool)
-> (PersistError -> PersistError -> Bool) -> Eq PersistError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersistError -> PersistError -> Bool
$c/= :: PersistError -> PersistError -> Bool
== :: PersistError -> PersistError -> Bool
$c== :: PersistError -> PersistError -> Bool
Eq, Int -> PersistError -> ShowS
[PersistError] -> ShowS
PersistError -> String
(Int -> PersistError -> ShowS)
-> (PersistError -> String)
-> ([PersistError] -> ShowS)
-> Show PersistError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersistError] -> ShowS
$cshowList :: [PersistError] -> ShowS
show :: PersistError -> String
$cshow :: PersistError -> String
showsPrec :: Int -> PersistError -> ShowS
$cshowsPrec :: Int -> PersistError -> ShowS
Show)
instance Reportable PersistError where
toReport :: PersistError -> Report
toReport = \case
Permission Text
path ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report Text
msg [Item [Text]
"PersistError.Permission:", Text
Item [Text]
path] Severity
Error
where
msg :: Text
msg =
[exon|Insufficient permissions for persistence file: #{path}|]
Decode Text
path Text
err ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report Text
msg [Item [Text]
"PersistError.Decode:", Text
Item [Text]
path, Text
Item [Text]
err] Severity
Error
where
msg :: Text
msg =
[exon|invalid data in persistence file, please delete it: #{path}|]
Path PersistPathError
err ->
PersistPathError -> Report
forall e. Reportable e => e -> Report
toReport PersistPathError
err