module Proteome.Data.ReplaceError where import Log (Severity (Error, Warn)) import Path (Abs, File, Path) import Ribosome (Report (Report), Reportable, toReport) import Ribosome (pathText) data ReplaceError = BadReplacement | CouldntLoadBuffer (Path Abs File) deriving stock (ReplaceError -> ReplaceError -> Bool (ReplaceError -> ReplaceError -> Bool) -> (ReplaceError -> ReplaceError -> Bool) -> Eq ReplaceError forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ReplaceError -> ReplaceError -> Bool $c/= :: ReplaceError -> ReplaceError -> Bool == :: ReplaceError -> ReplaceError -> Bool $c== :: ReplaceError -> ReplaceError -> Bool Eq, Int -> ReplaceError -> ShowS [ReplaceError] -> ShowS ReplaceError -> String (Int -> ReplaceError -> ShowS) -> (ReplaceError -> String) -> ([ReplaceError] -> ShowS) -> Show ReplaceError forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [ReplaceError] -> ShowS $cshowList :: [ReplaceError] -> ShowS show :: ReplaceError -> String $cshow :: ReplaceError -> String showsPrec :: Int -> ReplaceError -> ShowS $cshowsPrec :: Int -> ReplaceError -> ShowS Show) instance Reportable ReplaceError where toReport :: ReplaceError -> Report toReport ReplaceError BadReplacement = HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report Text "replacment line count does not match original" [Item [Text] "ReplaceError.BadReplacement"] Severity Warn toReport (CouldntLoadBuffer (Path Abs File -> Text forall b t. Path b t -> Text pathText -> Text path)) = HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report (Text "could not load file " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text path) [Item [Text] "ReplaceError.CouldntLoadBuffer", Text Item [Text] path] Severity Error