{-# LANGUAGE Rank2Types #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-| Defines the class @MonadFailure@ for monads which can fail. -} module Control.Monad.Failure.Class where import Control.Exception (throw, Exception) import Data.Typeable class Monad m => MonadFailure e m where failure :: e -> m a class MonadFailure e m => WrapFailure e m where -- | Wrap the failure value, if any, with the given function. This is -- useful in particular when you want all the exceptions returned from a -- certain library to be of a certain type, even if they were generated by -- a different library. wrapFailure :: (forall eIn. Exception eIn => eIn -> e) -> m a -> m a -- -------------- -- base instances -- -------------- instance MonadFailure e Maybe where failure _ = Nothing instance MonadFailure e [] where failure _ = [] instance Exception e => MonadFailure e IO where failure = Control.Exception.throw -- | Call 'failure' with a 'String'. failureString :: MonadFailure StringException m => String -> m a failureString = failure . StringException newtype StringException = StringException String deriving Typeable instance Show StringException where show (StringException s) = "StringException: " ++ s instance Exception StringException