lens-4.5: Lenses, Folds and Traversals

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

Control.Exception.Lens

Contents

Description

Control.Exception provides an example of a large open hierarchy that we can model with prisms and isomorphisms.

Additional combinators for working with IOException results can be found in System.IO.Error.Lens.

The combinators in this module have been generalized to work with MonadCatch instead of just IO. This enables them to be used more easily in Monad transformer stacks.

Synopsis

Handling

catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m rSource

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

>>> catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
 catching :: MonadCatch m => Prism' SomeException a     -> m r -> (a -> m r) -> m r
 catching :: MonadCatch m => Lens' SomeException a      -> m r -> (a -> m r) -> m r
 catching :: MonadCatch m => Traversal' SomeException a -> m r -> (a -> m r) -> m r
 catching :: MonadCatch m => Iso' SomeException a       -> m r -> (a -> m r) -> m r
 catching :: MonadCatch m => Getter SomeException a     -> m r -> (a -> m r) -> m r
 catching :: MonadCatch m => Fold SomeException a       -> m r -> (a -> m r) -> m r

catching_ :: MonadCatch m => Getting (First a) SomeException 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_ _AssertionFailed (assert False (return "uncaught")) $ return "caught"
"caught"
 catching_ :: MonadCatch m => Prism' SomeException a     -> m r -> m r -> m r
 catching_ :: MonadCatch m => Lens' SomeException a      -> m r -> m r -> m r
 catching_ :: MonadCatch m => Traversal' SomeException a -> m r -> m r -> m r
 catching_ :: MonadCatch m => Iso' SomeException a       -> m r -> m r -> m r
 catching_ :: MonadCatch m => Getter SomeException a     -> m r -> m r -> m r
 catching_ :: MonadCatch m => Fold SomeException a       -> m r -> m r -> m r

handling :: MonadCatch m => Getting (First a) SomeException 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 _NonTermination (\_ -> return "caught") $ throwIO NonTermination
"caught"
 handling :: MonadCatch m => Prism' SomeException a     -> (a -> m r) -> m r -> m r
 handling :: MonadCatch m => Lens' SomeException a      -> (a -> m r) -> m r -> m r
 handling :: MonadCatch m => Traversal' SomeException a -> (a -> m r) -> m r -> m r
 handling :: MonadCatch m => Iso' SomeException a       -> (a -> m r) -> m r -> m r
 handling :: MonadCatch m => Fold SomeException a       -> (a -> m r) -> m r -> m r
 handling :: MonadCatch m => Getter SomeException a     -> (a -> m r) -> m r -> m r

handling_ :: MonadCatch m => Getting (First a) SomeException 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_ _NonTermination (return "caught") $ throwIO NonTermination
"caught"
 handling_ :: MonadCatch m => Prism' SomeException a     -> m r -> m r -> m r
 handling_ :: MonadCatch m => Lens' SomeException a      -> m r -> m r -> m r
 handling_ :: MonadCatch m => Traversal' SomeException a -> m r -> m r -> m r
 handling_ :: MonadCatch m => Iso' SomeException a       -> m r -> m r -> m r
 handling_ :: MonadCatch m => Getter SomeException a     -> m r -> m r -> m r
 handling_ :: MonadCatch m => Fold SomeException a       -> m r -> m r -> m r

Trying

trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)Source

A variant of try that takes a Prism (or any Getter) to select which exceptions are caught (c.f. tryJust, catchJust). If the Exception does not match the predicate, it is re-thrown.

 trying :: MonadCatch m => Prism'     SomeException a -> m r -> m (Either a r)
 trying :: MonadCatch m => Lens'      SomeException a -> m r -> m (Either a r)
 trying :: MonadCatch m => Traversal' SomeException a -> m r -> m (Either a r)
 trying :: MonadCatch m => Iso'       SomeException a -> m r -> m (Either a r)
 trying :: MonadCatch m => Getter     SomeException a -> m r -> m (Either a r)
 trying :: MonadCatch m => Fold       SomeException a -> m r -> m (Either a r)

trying_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Maybe r)Source

A version of trying that discards the specific exception thrown.

 trying_ :: MonadCatch m => Prism'     SomeException a -> m r -> m (Maybe r)
 trying_ :: MonadCatch m => Lens'      SomeException a -> m r -> m (Maybe r)
 trying_ :: MonadCatch m => Traversal' SomeException a -> m r -> m (Maybe r)
 trying_ :: MonadCatch m => Iso'       SomeException a -> m r -> m (Maybe r)
 trying_ :: MonadCatch m => Getter     SomeException a -> m r -> m (Maybe r)
 trying_ :: MonadCatch m => Fold       SomeException a -> m r -> m (Maybe r)

Throwing

throwing :: AReview s SomeException a b -> b -> rSource

Throw an Exception described by a Prism. Exceptions may be thrown from purely functional code, but may only be caught within the IO Monad.

 throwing l ≡ reviews l throw
 throwing :: Prism' SomeException t -> t -> r
 throwing :: Iso' SomeException t   -> t -> r

throwingM :: MonadThrow m => AReview s SomeException a b -> b -> m rSource

A variant of throwing that can only be used within the IO Monad (or any other MonadCatch instance) to throw an Exception described by a Prism.

Although throwingM has a type that is a specialization of the type of throwing, the two functions are subtly different:

 throwing l e `seq` x  ≡ throwing e
 throwingM l e `seq` x ≡ x

The first example will cause the Exception e to be raised, whereas the second one won't. In fact, throwingM will only cause an Exception to be raised when it is used within the MonadCatch instance. The throwingM variant should be used in preference to throwing to raise an Exception within the Monad because it guarantees ordering with respect to other monadic operations, whereas throwing does not.

 throwingM l ≡ reviews l throw
 throwingM :: MonadThrow m => Prism' SomeException t -> t -> m r
 throwingM :: MonadThrow m => Iso' SomeException t   -> t -> m r

throwingTo :: MonadIO m => ThreadId -> AReview s SomeException a b -> b -> m ()Source

throwingTo raises an Exception specified by a Prism in the target thread.

 throwingTo thread l ≡ reviews l (throwTo thread)
 throwingTo :: ThreadId -> Prism' SomeException t -> t -> m a
 throwingTo :: ThreadId -> Iso' SomeException t   -> t -> m a

Mapping

mappedException :: (Exception e, Exception e') => Setter s s e e'Source

This Setter can be used to purely map over the Exceptions an arbitrary expression might throw; it is a variant of mapException in the same way that mapped is a variant of fmap.

 'mapException' ≡ 'over' 'mappedException'

This view that every Haskell expression can be regarded as carrying a bag of Exceptions is detailed in “A Semantics for Imprecise Exceptions” by Peyton Jones & al. at PLDI ’99.

The following maps failed assertions to arithmetic overflow:

>>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException %~ \ (AssertionFailed _) -> Overflow
"caught"

mappedException' :: Exception e' => Setter s s SomeException e'Source

This is a type restricted version of mappedException, which avoids the type ambiguity in the input Exception when using set.

The following maps any exception to arithmetic overflow:

>>> handling _Overflow (\_ -> return "caught") $ assert False (return "uncaught") & mappedException' .~ Overflow
"caught"

Exceptions

exception :: Exception a => Prism' SomeException aSource

Traverse the strongly typed Exception contained in SomeException where the type of your function matches the desired Exception.

 exception :: (Applicative f, Exception a)
           => (a -> f a) -> SomeException -> f SomeException

Exception Handlers

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

Instances

Handleable SomeException IO Handler 
Typeable1 m => Handleable SomeException m (Handler m) 
Handleable e m (Handler e m) 

IOExceptions

class AsIOException t whereSource

Exceptions that occur in the IO Monad. An IOException records a more specific error type, a descriptive string and maybe the handle that was used when the error was flagged.

Due to their richer structure relative to other exceptions, these have a more carefully overloaded signature.

Methods

_IOException :: Prism' t IOExceptionSource

Unfortunately the name ioException is taken by base for throwing IOExceptions.

 _IOException :: Prism' IOException IOException
 _IOException :: Prism' SomeException IOException

Many combinators for working with an IOException are available in System.IO.Error.Lens.

Instances

Arithmetic Exceptions

class AsArithException t whereSource

Arithmetic exceptions.

Methods

_ArithException :: Prism' t ArithExceptionSource

_Overflow :: AsArithException t => Prism' t ()Source

Handle arithmetic _Overflow.

 _Overflow_ArithException . _Overflow
 _Overflow :: Prism' ArithException ArithException
 _Overflow :: Prism' SomeException  ArithException

_Underflow :: AsArithException t => Prism' t ()Source

Handle arithmetic _Underflow.

 _Underflow_ArithException . _Underflow
 _Underflow :: Prism' ArithException ArithException
 _Underflow :: Prism' SomeException  ArithException

_LossOfPrecision :: AsArithException t => Prism' t ()Source

Handle arithmetic loss of precision.

 _LossOfPrecision_ArithException . _LossOfPrecision
 _LossOfPrecision :: Prism' ArithException ArithException
 _LossOfPrecision :: Prism' SomeException  ArithException

_DivideByZero :: AsArithException t => Prism' t ()Source

Handle division by zero.

 _DivideByZero_ArithException . _DivideByZero
 _DivideByZero :: Prism' ArithException ArithException
 _DivideByZero :: Prism' SomeException  ArithException

_Denormal :: AsArithException t => Prism' t ()Source

Handle exceptional _Denormalized floating pure.

 _Denormal_ArithException . _Denormal
 _Denormal :: Prism' ArithException ArithException
 _Denormal :: Prism' SomeException  ArithException

Array Exceptions

class AsArrayException t whereSource

Exceptions generated by array operations.

Methods

_ArrayException :: Prism' t ArrayExceptionSource

Extract information about an ArrayException.

 _ArrayException :: Prism' ArrayException ArrayException
 _ArrayException :: Prism' SomeException  ArrayException

_IndexOutOfBounds :: AsArrayException t => Prism' t StringSource

An attempt was made to index an array outside its declared bounds.

 _IndexOutOfBounds_ArrayException . _IndexOutOfBounds
 _IndexOutOfBounds :: Prism' ArrayException String
 _IndexOutOfBounds :: Prism' SomeException  String

_UndefinedElement :: AsArrayException t => Prism' t StringSource

An attempt was made to evaluate an element of an array that had not been initialized.

 _UndefinedElement_ArrayException . _UndefinedElement
 _UndefinedElement :: Prism' ArrayException String
 _UndefinedElement :: Prism' SomeException  String

Assertion Failed

class AsAssertionFailed t whereSource

assert was applied to False.

Methods

_AssertionFailed :: Prism' t StringSource

This Exception contains provides information about what assertion failed in the String.

>>> handling _AssertionFailed (\ xs -> "caught" <$ guard ("<interactive>" `isInfixOf` xs) ) $ assert False (return "uncaught")
"caught"
 _AssertionFailed :: Prism' AssertionFailed String
 _AssertionFailed :: Prism' SomeException   String

Async Exceptions

class AsAsyncException t whereSource

Asynchronous exceptions.

Methods

_AsyncException :: Prism' t AsyncExceptionSource

There are several types of AsyncException.

 _AsyncException :: Equality' AsyncException AsyncException
 _AsyncException :: Prism'    SomeException  AsyncException

_StackOverflow :: AsAsyncException t => Prism' t ()Source

The current thread's stack exceeded its limit. Since an Exception has been raised, the thread's stack will certainly be below its limit again, but the programmer should take remedial action immediately.

 _StackOverflow :: Prism' AsyncException ()
 _StackOverflow :: Prism' SomeException  ()

_HeapOverflow :: AsAsyncException t => Prism' t ()Source

The program's heap is reaching its limit, and the program should take action to reduce the amount of live data it has.

Notes:

  • It is undefined which thread receives this Exception.
  • GHC currently does not throw HeapOverflow exceptions.
 _HeapOverflow :: Prism' AsyncException ()
 _HeapOverflow :: Prism' SomeException  ()

_ThreadKilled :: AsAsyncException t => Prism' t ()Source

This Exception is raised by another thread calling killThread, or by the system if it needs to terminate the thread for some reason.

 _ThreadKilled :: Prism' AsyncException ()
 _ThreadKilled :: Prism' SomeException  ()

_UserInterrupt :: AsAsyncException t => Prism' t ()Source

This Exception is raised by default in the main thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console).

 _UserInterrupt :: Prism' AsyncException ()
 _UserInterrupt :: Prism' SomeException  ()

Non-Termination

class AsNonTermination t whereSource

Thrown when the runtime system detects that the computation is guaranteed not to terminate. Note that there is no guarantee that the runtime system will notice whether any given computation is guaranteed to terminate or not.

Methods

_NonTermination :: Prism' t ()Source

There is no additional information carried in a NonTermination Exception.

 _NonTermination :: Prism' NonTermination ()
 _NonTermination :: Prism' SomeException  ()

Nested Atomically

class AsNestedAtomically t whereSource

Thrown when the program attempts to call atomically, from the STM package, inside another call to atomically.

Methods

_NestedAtomically :: Prism' t ()Source

There is no additional information carried in a NestedAtomically Exception.

 _NestedAtomically :: Prism' NestedAtomically ()
 _NestedAtomically :: Prism' SomeException    ()

Blocked Indefinitely

on MVar

class AsBlockedIndefinitelyOnMVar t whereSource

The thread is blocked on an MVar, but there are no other references to the MVar so it can't ever continue.

Methods

_BlockedIndefinitelyOnMVar :: Prism' t ()Source

There is no additional information carried in a BlockedIndefinitelyOnMVar Exception.

 _BlockedIndefinitelyOnMVar :: Prism' BlockedIndefinitelyOnMVar ()
 _BlockedIndefinitelyOnMVar :: Prism' SomeException             ()

on STM

class AsBlockedIndefinitelyOnSTM t whereSource

The thread is waiting to retry an STM transaction, but there are no other references to any TVars involved, so it can't ever continue.

Methods

_BlockedIndefinitelyOnSTM :: Prism' t ()Source

There is no additional information carried in a BlockedIndefinitelyOnSTM Exception.

 _BlockedIndefinitelyOnSTM :: Prism' BlockedIndefinitelyOnSTM ()
 _BlockedIndefinitelyOnSTM :: Prism' SomeException            ()

Deadlock

class AsDeadlock t whereSource

There are no runnable threads, so the program is deadlocked. The Deadlock Exception is raised in the main thread only.

Methods

_Deadlock :: Prism' t ()Source

There is no information carried in a Deadlock Exception.

 _Deadlock :: Prism' Deadlock      ()
 _Deadlock :: Prism' SomeException ()

Instances

No Such Method

class AsNoMethodError t whereSource

A class method without a definition (neither a default definition, nor a definition in the appropriate instance) was called.

Methods

_NoMethodError :: Prism' t StringSource

Extract a description of the missing method.

 _NoMethodError :: Prism' NoMethodError String
 _NoMethodError :: Prism' SomeException String

Pattern Match Failure

class AsPatternMatchFail t whereSource

A pattern match failed.

Methods

_PatternMatchFail :: Prism' t StringSource

Information about the source location of the pattern.

 _PatternMatchFail :: Prism' PatternMatchFail String
 _PatternMatchFail :: Prism' SomeException    String

Record

class AsRecConError t whereSource

An uninitialised record field was used.

Methods

_RecConError :: Prism' t StringSource

Information about the source location where the record was constructed.

 _RecConError :: Prism' RecConError   String
 _RecConError :: Prism' SomeException String

Instances

class AsRecSelError t whereSource

A record selector was applied to a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.

Methods

_RecSelError :: Prism' t StringSource

Information about the source location where the record selection occurred.

Instances

class AsRecUpdError t whereSource

A record update was performed on a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.

Methods

_RecUpdError :: Prism' t StringSource

Information about the source location where the record was updated.

Instances

Error Call

class AsErrorCall t whereSource

This is thrown when the user calls error.

Methods

_ErrorCall :: Prism' t StringSource

Retrieve the argument given to error.

ErrorCall is isomorphic to a String.

>>> catching _ErrorCall (error "touch down!") return
"touch down!"

Instances

Handling Exceptions

class AsHandlingException t whereSource

This Exception is thrown by lens when the user somehow manages to rethrow an internal HandlingException.