| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
RIO.PrettyPrint.PrettyException
Description
This module provides a type representing pretty exceptions. It can be used as in the example below:
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where
import RIO
( Exception, Handler (..), IO, RIO, Show, SomeException (..), Typeable
, ($), catches, displayException, exitFailure, fromString, logError
, mempty, throwIO
)
import RIO.PrettyPrint
( Pretty (..), Style (..), (<+>), prettyError, prettyInfo, style )
import RIO.PrettyPrint.PrettyException ( PrettyException (..) )
import RIO.PrettyPrint.Simple ( SimplePrettyApp, runSimplePrettyApp )
main :: IO ()
main = runSimplePrettyApp 80 mempty (action `catches` handleExceptions)
where
action :: RIO SimplePrettyApp ()
action = do
prettyInfo "Running action!"
throwIO (PrettyException MyPrettyException)
handleExceptions :: [Handler (RIO SimplePrettyApp) ()]
handleExceptions =
[ Handler handlePrettyException
, Handler handleSomeException
]
handlePrettyException :: PrettyException -> RIO SimplePrettyApp ()
handlePrettyException e = do
prettyError $ pretty e
exitFailure
handleSomeException :: SomeException -> RIO SimplePrettyApp ()
handleSomeException (SomeException e) = do
logError $ fromString $ displayException e
exitFailure
data MyPrettyException
= MyPrettyException
deriving (Show, Typeable)
instance Pretty MyPrettyException where
pretty MyPrettyException =
"My" <+> style Highlight "pretty" <+> "exception!"
instance Exception MyPrettyExceptionSynopsis
- data PrettyException = forall e.(Exception e, Pretty e) => PrettyException e
- ppException :: SomeException -> StyleDoc
- prettyThrowIO :: (Exception e, MonadIO m, Pretty e) => e -> m a
- prettyThrowM :: (Exception e, MonadThrow m, Pretty e) => e -> m a
Documentation
data PrettyException Source #
Type representing pretty exceptions.
Since: 0.1.4.0
Constructors
| forall e.(Exception e, Pretty e) => PrettyException e |
Instances
| Exception PrettyException Source # | |
Defined in RIO.PrettyPrint.PrettyException Methods toException :: PrettyException -> SomeException # | |
| Show PrettyException Source # | |
Defined in RIO.PrettyPrint.PrettyException Methods showsPrec :: Int -> PrettyException -> ShowS # show :: PrettyException -> String # showList :: [PrettyException] -> ShowS # | |
| Pretty PrettyException Source # | |
Defined in RIO.PrettyPrint.PrettyException Methods pretty :: PrettyException -> StyleDoc Source # | |
ppException :: SomeException -> StyleDoc Source #
Provide the prettiest available information about an exception.
prettyThrowIO :: (Exception e, MonadIO m, Pretty e) => e -> m a Source #
Synchronously throw the given exception as a PrettyException.
prettyThrowM :: (Exception e, MonadThrow m, Pretty e) => e -> m a Source #
Throw the given exception as a PrettyException, when the action is run in
the monad m.