lens-4.0.7: Lenses, Folds and Traversals

PortabilityControl.Monad.Error
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Monad.Error.Lens

Contents

Description

 

Synopsis

Catching

catching :: MonadError e m => Getting (First a) e a -> m r -> (a -> m r) -> m rSource

Catch exceptions that match a given Prism (or any Getter, really).

 catching :: MonadError e m => Prism' e a     -> m r -> (a -> m r) -> m r
 catching :: MonadError e m => Lens' e a      -> m r -> (a -> m r) -> m r
 catching :: MonadError e m => Traversal' e a -> m r -> (a -> m r) -> m r
 catching :: MonadError e m => Iso' e a       -> m r -> (a -> m r) -> m r
 catching :: MonadError e m => Getter e a     -> m r -> (a -> m r) -> m r
 catching :: MonadError e m => Fold e a       -> m r -> (a -> m r) -> m r

catching_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m rSource

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 () where the result of the Prism or Fold isn't particularly valuable, just the fact that it matches.

 catching_ :: MonadError e m => Prism' e a     -> m r -> m r -> m r
 catching_ :: MonadError e m => Lens' e a      -> m r -> m r -> m r
 catching_ :: MonadError e m => Traversal' e a -> m r -> m r -> m r
 catching_ :: MonadError e m => Iso' e a       -> m r -> m r -> m r
 catching_ :: MonadError e m => Getter e a     -> m r -> m r -> m r
 catching_ :: MonadError e m => Fold e a       -> m r -> m r -> m r

Handling

handling :: MonadError e m => Getting (First a) e a -> (a -> m r) -> m r -> m rSource

A version of catching with the arguments swapped around; useful in situations where the code for the handler is shorter.

 handling :: MonadError e m => Prism' e a     -> (a -> m r) -> m r -> m r
 handling :: MonadError e m => Lens' e a      -> (a -> m r) -> m r -> m r
 handling :: MonadError e m => Traversal' e a -> (a -> m r) -> m r -> m r
 handling :: MonadError e m => Iso' e a       -> (a -> m r) -> m r -> m r
 handling :: MonadError e m => Fold e a       -> (a -> m r) -> m r -> m r
 handling :: MonadError e m => Getter e a     -> (a -> m r) -> m r -> m r

handling_ :: MonadError e m => Getting (First a) e a -> m r -> m r -> m rSource

A version of catching_ with the arguments swapped around; useful in situations where the code for the handler is shorter.

 handling_ :: MonadError e m => Prism' e a     -> m r -> m r -> m r
 handling_ :: MonadError e m => Lens' e a      -> m r -> m r -> m r
 handling_ :: MonadError e m => Traversal' e a -> m r -> m r -> m r
 handling_ :: MonadError e m => Iso' e a       -> m r -> m r -> m r
 handling_ :: MonadError e m => Getter e a     -> m r -> m r -> m r
 handling_ :: MonadError e m => Fold e 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 :: MonadError e m => Prism' e a     -> m r -> m (Either a r)
 trying :: MonadError e m => Lens' e a      -> m r -> m (Either a r)
 trying :: MonadError e m => Traversal' e a -> m r -> m (Either a r)
 trying :: MonadError e m => Iso' e a       -> m r -> m (Either a r)
 trying :: MonadError e m => Getter e a     -> m r -> m (Either a r)
 trying :: MonadError e m => Fold e a       -> m r -> m (Either a r)

Handlers

catches :: MonadError e m => m a -> [Handler e m a] -> m aSource

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 = catches expr [ handler _Foo handleFoo
                  , handler _Bar handleBar
                  ]

data Handler e m r Source

You need this when using catches.

Constructors

forall a . Handler (e -> Maybe a) (a -> m r) 

Instances

Handleable e m (Handler e m) 
Monad m => Functor (Handler e m) 
Monad m => Plus (Handler e m) 
Monad m => Alt (Handler e m) 
Monad m => Monoid (Handler e m a) 
Monad m => Semigroup (Handler e m a) 

class Handleable e m h | h -> e m whereSource

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.

Methods

handler :: Typeable a => Getting (First a) e a -> (a -> m r) -> h rSource

This builds a Handler for just the targets of a given Prism (or any Getter, really).

 catches ... [ handler _AssertionFailed (s -> print $ "Assertion Failed\n" ++ s)
             , handler _ErrorCall (s -> print $ "Error\n" ++ s)
             ]

This works ith both the Handler type provided by Control.Exception:

 handler :: Getter     SomeException a -> (a -> IO r) -> Handler r
 handler :: Fold       SomeException a -> (a -> IO r) -> Handler r
 handler :: Prism'     SomeException a -> (a -> IO r) -> Handler r
 handler :: Lens'      SomeException a -> (a -> IO r) -> Handler r
 handler :: Traversal' SomeException a -> (a -> IO r) -> Handler r

and with the Handler type provided by Control.Monad.Catch:

 handler :: Getter     SomeException a -> (a -> m r) -> Handler m r
 handler :: Fold       SomeException a -> (a -> m r) -> Handler m r
 handler :: Prism'     SomeException a -> (a -> m r) -> Handler m r
 handler :: Lens'      SomeException a -> (a -> m r) -> Handler m r
 handler :: Traversal' SomeException a -> (a -> m r) -> Handler m r

and with the Handler type provided by Control.Monad.Error.Lens:

 handler :: Getter     e a -> (a -> m r) -> Handler e m r
 handler :: Fold       e a -> (a -> m r) -> Handler e m r
 handler :: Prism'     e a -> (a -> m r) -> Handler e m r
 handler :: Lens'      e a -> (a -> m r) -> Handler e m r
 handler :: Traversal' e a -> (a -> m r) -> Handler e m r

handler_ :: Typeable a => Getting (First a) e a -> m r -> h rSource

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_ :: Getter     SomeException a -> IO r -> Handler r
 handler_ :: Fold       SomeException a -> IO r -> Handler r
 handler_ :: Prism'     SomeException a -> IO r -> Handler r
 handler_ :: Lens'      SomeException a -> IO r -> Handler r
 handler_ :: Traversal' SomeException a -> IO r -> Handler r

and with the Handler type provided by Control.Monad.Catch:

 handler_ :: Getter     SomeException a -> m r -> Handler m r
 handler_ :: Fold       SomeException a -> m r -> Handler m r
 handler_ :: Prism'     SomeException a -> m r -> Handler m r
 handler_ :: Lens'      SomeException a -> m r -> Handler m r
 handler_ :: Traversal' SomeException a -> m r -> Handler m r

and with the Handler type provided by Control.Monad.Error.Lens:

 handler_ :: Getter     e a -> m r -> Handler e m r
 handler_ :: Fold       e a -> m r -> Handler e m r
 handler_ :: Prism'     e a -> m r -> Handler e m r
 handler_ :: Lens'      e a -> m r -> Handler e m r
 handler_ :: Traversal' e a -> m r -> Handler e m r

Throwing

throwing :: MonadError e m => AReview e e t t -> t -> m xSource

Throw an Exception described by a Prism.

throwing l ≡ reviews l throwError
 throwing :: MonadError e m => Prism' e t -> t -> a
 throwing :: MonadError e m => Iso' e t   -> t -> a