exception-via-0.2.0.0: DerivingVia for your hierarchical exceptions
Safe HaskellSafe-Inferred
LanguageHaskell2010

ExceptionVia

Description

Hierarchical exceptions are a powerful and useful tool in the Haskell toolbox, but they're not used anywhere near often enough. I suspect it's because they're a) not very commonly understood and b) a lot of boilerplate to write. This library is intended to help the latter problem.

Let's look at an example. We'll define a type for all of our application's exceptions:

data AppException where
  AppException :: Exception e => AppException

deriving stock instance Show AppException

instance Exception AppException

mkHierarchy ''AppException

Now, we can try to catch all of the Exceptions that we define ourselves:

tryApp :: IO a -> IO (Either AppException a)
tryApp = try

Now let's define a problem that might happen in our domain. We're going to derive Exception through our subtype wrapper.

data HttpException = HttpException
  deriving stock Show
  deriving
    via (HttpException <!!! AppException)
      Exception HttpException

Now, we can throw an HttpException, and catch it as part of AppException:

throwHttp :: IO x
throwHttp = throwIO HttpException

main = do
  eresult <- tryApp throwHttp
  case result of
    Left (AppException err) ->
      putStrLn "I caught it!"
    Right _ ->
      putStrLn "Wait what??

For each "step" in the hierarchy, you define a GADT like AppException above. Define an instance of Hierarchy for it, either via the Template Haskell helper mkHierarchy, or manually.

Synopsis

Deriving Via Helpers

type (<!!!) lil big = ExceptionVia big lil Source #

A concise operator alias for ExceptionVia.

Given a wrapper exception type like SomeCompilerException, you can derive an instance of Exception like so:

data MismatchedParentheses = MismatchedParentheses
  deriving stock Show
  deriving
    via (MismatchedParentheses <!!! SomeCompilerException)
      Exception MismatchedParentheses

Since: 0.1.0.0

newtype ExceptionVia big lil Source #

This is the explicit word version of (<!!!). You can use this if you don't like TypeOperators.

Given a wrapper exception type like SomeCompilerException, you can derive an instance of Exception like so:

data MismatchedParentheses = MismatchedParentheses
  deriving stock Show
  deriving
    via (ExceptionVia SomeCompilerException MismatchedParentheses)
      Exception MismatchedParentheses

Since: 0.1.0.0

Constructors

ExceptionVia 

Fields

Instances

Instances details
(Hierarchy big, Exception big, Exception lil) => Exception (ExceptionVia big lil) Source # 
Instance details

Defined in ExceptionVia

Show lil => Show (ExceptionVia big lil) Source # 
Instance details

Defined in ExceptionVia

Methods

showsPrec :: Int -> ExceptionVia big lil -> ShowS #

show :: ExceptionVia big lil -> String #

showList :: [ExceptionVia big lil] -> ShowS #

Establishing Hierarchy

mkHierarchy :: Name -> DecsQ Source #

Create a boilerplate Hierarchy instance for a type given a name.

This code block defines an exception wrapper type and an accompanying Hierarchy instance.

data ExceptionWrapper where
  ExceptionWrapper :: Exception e => e -> ExceptionWrapper

mkHierarchy ''ExceptionWrapper

Since: 0.1.0.0

class Typeable big => Hierarchy big where Source #

This class tells us how to wrap and unwrap values from our hierarchical wrapper types. It is very similar to Exception, but instead of specifying how to put some value into a SomeException or cast a value from a SomeException, we say how to put any value into this big type or cast any value out of the big type.

Instances are very straightforward. For any type:

data ExceptionWrapper where
  ExceptionWrapper :: Exception e => e -> ExceptionWrapper

The instance will look like this:

instance Hierarchy ExceptionWrapper where
  toParent = ExceptionWrapper
  fromParent (ExceptionWrapper e) = cast e

You can skip the boilerplate with the mkHierarchy Template Haskell function.

Since: 0.1.0.0

Methods

toParent :: Exception lil => lil -> big Source #

Given any Exceptional value, wrap it up in the big type.

Since: 0.1.0.0

fromParent :: Exception lil => big -> Maybe lil Source #

Given a big type, cast out the Exception buried within. Will return Nothing if the requested type is different from the actual contained value.

Since: 0.1.0.0