rio-prettyprint-0.1.3.0: Pretty-printing for RIO
Safe HaskellSafe-Inferred
LanguageHaskell2010

RIO.PrettyPrint.PrettyException

Description

This module provides a type representing pretty exceptions. It can be used as in the example below:



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 MyPrettyException
Synopsis

Documentation