lens-3.8.0.1: Lenses, Folds and Traversals

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

Control.Monad.Error.Lens

Contents

Description

 

Synopsis

Catching

catching :: MonadError e m => Getting (First a) e t a b -> 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 t a b -> 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 t a b -> (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 t a b -> 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 t a b -> 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)

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