| Copyright | (C) 2014-2016 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Control.Monad.Error | 
| Safe Haskell | Safe | 
| Language | Haskell98 | 
Control.Monad.Error.Lens
Description
Synopsis
- catching :: MonadError e m => Getting (First a) e a -> m r -> (a -> m r) -> m r
- catching_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r
- handling :: MonadError e m => Getting (First a) e a -> (a -> m r) -> m r -> m r
- handling_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r
- trying :: MonadError e m => Getting (First a) e a -> m r -> m (Either a r)
- catches :: MonadError e m => m a -> [Handler e m a] -> m a
- data Handler e m r = Handler (e -> Maybe a) (a -> m r)
- class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where
- throwing :: MonadError e m => AReview e t -> t -> m x
- throwing_ :: MonadError e m => AReview e () -> m x
Catching
catching :: MonadError e m => Getting (First a) e a -> m r -> (a -> m r) -> m r Source #
Catch exceptions that match a given Prism (or any Getter, really).
catching::MonadErrore m =>Prism'e a -> m r -> (a -> m r) -> m rcatching::MonadErrore m =>Lens'e a -> m r -> (a -> m r) -> m rcatching::MonadErrore m =>Traversal'e a -> m r -> (a -> m r) -> m rcatching::MonadErrore m =>Iso'e a -> m r -> (a -> m r) -> m rcatching::MonadErrore m =>Gettere a -> m r -> (a -> m r) -> m rcatching::MonadErrore m =>Folde a -> m r -> (a -> m r) -> m r
catching_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r Source #
Catch exceptions that match a given Prism (or any Getter), discarding
 the information about the match. This is particuarly useful when you have
 a Prism' e ()Prism or Fold isn't
 particularly valuable, just the fact that it matches.
catching_::MonadErrore m =>Prism'e a -> m r -> m r -> m rcatching_::MonadErrore m =>Lens'e a -> m r -> m r -> m rcatching_::MonadErrore m =>Traversal'e a -> m r -> m r -> m rcatching_::MonadErrore m =>Iso'e a -> m r -> m r -> m rcatching_::MonadErrore m =>Gettere a -> m r -> m r -> m rcatching_::MonadErrore m =>Folde a -> m r -> m r -> m r
Handling
handling :: MonadError e m => Getting (First a) e a -> (a -> m r) -> m r -> m r Source #
A version of catching with the arguments swapped around; useful in
 situations where the code for the handler is shorter.
handling::MonadErrore m =>Prism'e a -> (a -> m r) -> m r -> m rhandling::MonadErrore m =>Lens'e a -> (a -> m r) -> m r -> m rhandling::MonadErrore m =>Traversal'e a -> (a -> m r) -> m r -> m rhandling::MonadErrore m =>Iso'e a -> (a -> m r) -> m r -> m rhandling::MonadErrore m =>Folde a -> (a -> m r) -> m r -> m rhandling::MonadErrore m =>Gettere a -> (a -> m r) -> m r -> m r
handling_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m r Source #
A version of catching_ with the arguments swapped around; useful in
 situations where the code for the handler is shorter.
handling_::MonadErrore m =>Prism'e a -> m r -> m r -> m rhandling_::MonadErrore m =>Lens'e a -> m r -> m r -> m rhandling_::MonadErrore m =>Traversal'e a -> m r -> m r -> m rhandling_::MonadErrore m =>Iso'e a -> m r -> m r -> m rhandling_::MonadErrore m =>Gettere a -> m r -> m r -> m rhandling_::MonadErrore m =>Folde a -> m r -> m r -> m r
Trying
trying :: MonadError e m => Getting (First a) e a -> m r -> m (Either a r) Source #
trying takes a Prism (or any Getter) to select which exceptions are caught
 If the Exception does not match the predicate, it is re-thrown.
trying::MonadErrore m =>Prism'e a -> m r -> m (Eithera r)trying::MonadErrore m =>Lens'e a -> m r -> m (Eithera r)trying::MonadErrore m =>Traversal'e a -> m r -> m (Eithera r)trying::MonadErrore m =>Iso'e a -> m r -> m (Eithera r)trying::MonadErrore m =>Gettere a -> m r -> m (Eithera r)trying::MonadErrore m =>Folde a -> m r -> m (Eithera r)
Handlers
catches :: MonadError e m => m a -> [Handler e m a] -> m a Source #
This function exists to remedy a gap between the functionality of Control.Exception
 and Control.Monad.Error. Control.Exception supplies catches and
 a notion of Handler, which we duplicate here in a form suitable for
 working with any MonadError instance.
Sometimes you want to catch two different sorts of error. You could do something like
f =handling_Foo handleFoo (handling_Bar handleBar expr)
However, there are a couple of problems with this approach. The first is
 that having two exception handlers is inefficient. However, the more
 serious issue is that the second exception handler will catch exceptions
 in the first, e.g. in the example above, if handleFoo uses throwError
 then the second exception handler will catch it.
Instead, we provide a function catches, which would be used thus:
f =catchesexpr [handler_Foo handleFoo ,handler_Bar handleBar ]
You need this when using catches.
class Handleable e (m :: * -> *) (h :: * -> *) | h -> e m where Source #
Both exceptions and Control.Exception provide a Handler type.
This lets us write combinators to build handlers that are agnostic about the choice of which of these they use.
Minimal complete definition
Methods
handler :: Typeable a => Getting (First a) e a -> (a -> m r) -> h r Source #
This builds a Handler for just the targets of a given Prism (or any Getter, really).
catches... [handler_AssertionFailed(s ->$"Assertion Failed\n"++s) ,handler_ErrorCall(s ->$"Error\n"++s) ]
This works ith both the Handler type provided by Control.Exception:
handler::GetterSomeExceptiona -> (a ->IOr) ->Handlerrhandler::FoldSomeExceptiona -> (a ->IOr) ->Handlerrhandler::Prism'SomeExceptiona -> (a ->IOr) ->Handlerrhandler::Lens'SomeExceptiona -> (a ->IOr) ->Handlerrhandler::Traversal'SomeExceptiona -> (a ->IOr) ->Handlerr
and with the Handler type provided by Control.Monad.Catch:
handler::GetterSomeExceptiona -> (a -> m r) ->Handlerm rhandler::FoldSomeExceptiona -> (a -> m r) ->Handlerm rhandler::Prism'SomeExceptiona -> (a -> m r) ->Handlerm rhandler::Lens'SomeExceptiona -> (a -> m r) ->Handlerm rhandler::Traversal'SomeExceptiona -> (a -> m r) ->Handlerm r
and with the Handler type provided by Control.Monad.Error.Lens:
handler::Gettere a -> (a -> m r) ->Handlere m rhandler::Folde a -> (a -> m r) ->Handlere m rhandler::Prism'e a -> (a -> m r) ->Handlere m rhandler::Lens'e a -> (a -> m r) ->Handlere m rhandler::Traversal'e a -> (a -> m r) ->Handlere m r
handler_ :: Typeable a => Getting (First a) e a -> m r -> h r Source #
This builds a Handler for just the targets of a given Prism (or any Getter, really).
 that ignores its input and just recovers with the stated monadic action.
catches... [handler__NonTermination(return"looped") ,handler__StackOverflow(return"overflow") ]
This works with the Handler type provided by Control.Exception:
handler_::GetterSomeExceptiona ->IOr ->Handlerrhandler_::FoldSomeExceptiona ->IOr ->Handlerrhandler_::Prism'SomeExceptiona ->IOr ->Handlerrhandler_::Lens'SomeExceptiona ->IOr ->Handlerrhandler_::Traversal'SomeExceptiona ->IOr ->Handlerr
and with the Handler type provided by Control.Monad.Catch:
handler_::GetterSomeExceptiona -> m r ->Handlerm rhandler_::FoldSomeExceptiona -> m r ->Handlerm rhandler_::Prism'SomeExceptiona -> m r ->Handlerm rhandler_::Lens'SomeExceptiona -> m r ->Handlerm rhandler_::Traversal'SomeExceptiona -> m r ->Handlerm r
and with the Handler type provided by Control.Monad.Error.Lens:
handler_::Gettere a -> m r ->Handlere m rhandler_::Folde a -> m r ->Handlere m rhandler_::Prism'e a -> m r ->Handlere m rhandler_::Lens'e a -> m r ->Handlere m rhandler_::Traversal'e a -> m r ->Handlere m r
Instances
| Handleable SomeException IO Handler Source # | |
| Typeable (* -> *) m => Handleable SomeException m (Handler m) Source # | |
| Handleable e m (Handler e m) Source # | |
Throwing
throwing :: MonadError e m => AReview e t -> t -> m x Source #
Throw an Exception described by a Prism.
throwingl ≡reviewslthrowError
throwing::MonadErrore m =>Prism'e t -> t -> athrowing::MonadErrore m =>Iso'e t -> t -> a
throwing_ :: MonadError e m => AReview e () -> m x Source #
Similar to throwing but specialised for the common case of
   error constructors with no arguments.
data MyError = Foo | Bar makePrisms ''MyErrorthrowing__Foo ::MonadErrorMyError m => m a