module Proteome.Data.GrepError where import Exon (exon) import Log (Severity (Warn)) import Path (Abs, Dir, Path) import Ribosome (Report (Report), Reportable (toReport), pathText) data GrepError = Empty | NotInPath Text | NoSuchExecutable Text | NoSuchDestination (Path Abs Dir) | EmptyUserInput Text deriving stock (GrepError -> GrepError -> Bool (GrepError -> GrepError -> Bool) -> (GrepError -> GrepError -> Bool) -> Eq GrepError forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: GrepError -> GrepError -> Bool $c/= :: GrepError -> GrepError -> Bool == :: GrepError -> GrepError -> Bool $c== :: GrepError -> GrepError -> Bool Eq, Int -> GrepError -> ShowS [GrepError] -> ShowS GrepError -> String (Int -> GrepError -> ShowS) -> (GrepError -> String) -> ([GrepError] -> ShowS) -> Show GrepError forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [GrepError] -> ShowS $cshowList :: [GrepError] -> ShowS show :: GrepError -> String $cshow :: GrepError -> String showsPrec :: Int -> GrepError -> ShowS $cshowsPrec :: Int -> GrepError -> ShowS Show) instance Reportable GrepError where toReport :: GrepError -> Report toReport = \case GrepError Empty -> HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report Text "grep cmdline is empty" [Item [Text] "GrepError.Empty"] Severity Warn NotInPath Text exe -> HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report (Text "grep executable `" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text exe Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "` not found in $PATH") [Item [Text] "GrepError.NotInPath:", Text Item [Text] exe] Severity Warn NoSuchExecutable Text exe -> HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report (Text "grep executable `" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text exe Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "` does not exist") [Item [Text] "GrepError.NoSuchExecutable:", Text Item [Text] exe] Severity Warn NoSuchDestination (Path Abs Dir -> Text forall b t. Path b t -> Text pathText -> Text dir) -> HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report [exon|grep destination `#{dir}` does not exist|] [Item [Text] "GrepError.NoSuchDestination:", Text Item [Text] dir] Severity Warn EmptyUserInput Text what -> HasCallStack => Text -> [Text] -> Severity -> Report Text -> [Text] -> Severity -> Report Report [exon|no #{what} given|] [Item [Text] "GrepError.EmptyPattern"] Severity Warn