lens-5.3.2: Lenses, Folds and Traversals
Copyright(C) 2012-16 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityControl.Exception
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Exception.Lens

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 r Source #

Catch exceptions that match a given Prism (or any Fold, 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 r Source #

Catch exceptions that match a given Prism (or any Getter), discarding the information about the match. This is particularly 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 r Source #

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 r Source #

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 Fold) 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 SomeException b -> b -> r Source #

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

throwing_ :: AReview SomeException () -> m x Source #

Similar to throwing but specialised for the common case of error constructors with no arguments.

data MyError = Foo | Bar
makePrisms ''MyError
throwing_ _Foo :: MonadError MyError m => m a

throwingM :: MonadThrow m => AReview SomeException b -> b -> m r Source #

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 SomeException 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 a Source #

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

pattern Exception :: Exception a => a -> SomeException Source #

Exception Handlers

class Handleable e (m :: Type -> Type) (h :: Type -> Type) | 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

handler

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 -> 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 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_ :: 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

Instances details
Handleable SomeException IO Handler Source # 
Instance details

Defined in Control.Lens.Internal.Exception

Methods

handler :: Typeable a => Getting (First a) SomeException a -> (a -> IO r) -> Handler r Source #

handler_ :: Typeable a => Getting (First a) SomeException a -> IO r -> Handler r Source #

Typeable m => Handleable SomeException m (Handler m) Source # 
Instance details

Defined in Control.Lens.Internal.Exception

Methods

handler :: Typeable a => Getting (First a) SomeException a -> (a -> m r) -> Handler m r Source #

handler_ :: Typeable a => Getting (First a) SomeException a -> m r -> Handler m r Source #

Handleable e m (Handler e m) Source # 
Instance details

Defined in Control.Monad.Error.Lens

Methods

handler :: Typeable a => Getting (First a) e a -> (a -> m r) -> Handler e m r Source #

handler_ :: Typeable a => Getting (First a) e a -> m r -> Handler e m r Source #

IOExceptions

class AsIOException t where Source #

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 IOException Source #

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

Instances details
AsIOException SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_IOException :: Prism' SomeException IOException Source #

AsIOException IOException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_IOException :: Prism' IOException IOException Source #

pattern IOException_ :: AsIOException s => IOException -> s Source #

Arithmetic Exceptions

class AsArithException t where Source #

Arithmetic exceptions.

Methods

_ArithException :: Prism' t ArithException Source #

_ArithException :: Prism' ArithException ArithException
_ArithException :: Prism' SomeException  ArithException

Instances

Instances details
AsArithException ArithException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_ArithException :: Prism' ArithException ArithException Source #

AsArithException SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_ArithException :: Prism' SomeException ArithException Source #

_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

pattern ArithException_ :: AsArithException s => ArithException -> s Source #

Array Exceptions

class AsArrayException t where Source #

Exceptions generated by array operations.

Methods

_ArrayException :: Prism' t ArrayException Source #

Extract information about an ArrayException.

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

Instances

Instances details
AsArrayException SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_ArrayException :: Prism' SomeException ArrayException Source #

AsArrayException ArrayException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_ArrayException :: Prism' ArrayException ArrayException Source #

_IndexOutOfBounds :: AsArrayException t => Prism' t String Source #

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 String Source #

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

pattern ArrayException_ :: AsArrayException s => ArrayException -> s Source #

pattern IndexOutOfBounds_ :: AsArrayException s => String -> s Source #

pattern UndefinedElement_ :: AsArrayException s => String -> s Source #

Assertion Failed

class AsAssertionFailed t where Source #

assert was applied to False.

Minimal complete definition

__AssertionFailed

Methods

__AssertionFailed :: Prism' t AssertionFailed Source #

__AssertionFailed :: Prism' AssertionFailed AssertionFailed
__AssertionFailed :: Prism' SomeException   AssertionFailed

_AssertionFailed :: Prism' t String Source #

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

Instances

Instances details
AsAssertionFailed SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__AssertionFailed :: Prism' SomeException AssertionFailed Source #

_AssertionFailed :: Prism' SomeException String Source #

AsAssertionFailed AssertionFailed Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__AssertionFailed :: Prism' AssertionFailed AssertionFailed Source #

_AssertionFailed :: Prism' AssertionFailed String Source #

pattern AssertionFailed__ :: AsAssertionFailed s => AssertionFailed -> s Source #

pattern AssertionFailed_ :: AsAssertionFailed s => String -> s Source #

Async Exceptions

class AsAsyncException t where Source #

Asynchronous exceptions.

Methods

_AsyncException :: Prism' t AsyncException Source #

There are several types of AsyncException.

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

Instances

Instances details
AsAsyncException SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_AsyncException :: Prism' SomeException AsyncException Source #

AsAsyncException AsyncException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

_AsyncException :: Prism' AsyncException AsyncException Source #

_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  ()

pattern AsyncException_ :: AsAsyncException s => AsyncException -> s Source #

Non-Termination

class AsNonTermination t where Source #

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.

Minimal complete definition

__NonTermination

Methods

__NonTermination :: Prism' t NonTermination Source #

__NonTermination :: Prism' NonTermination NonTermination
__NonTermination :: Prism' SomeException  NonTermination

_NonTermination :: Prism' t () Source #

There is no additional information carried in a NonTermination Exception.

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

Instances

Instances details
AsNonTermination NonTermination Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NonTermination :: Prism' NonTermination NonTermination Source #

_NonTermination :: Prism' NonTermination () Source #

AsNonTermination SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NonTermination :: Prism' SomeException NonTermination Source #

_NonTermination :: Prism' SomeException () Source #

pattern NonTermination__ :: AsNonTermination s => NonTermination -> s Source #

Nested Atomically

class AsNestedAtomically t where Source #

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

Minimal complete definition

__NestedAtomically

Methods

__NestedAtomically :: Prism' t NestedAtomically Source #

__NestedAtomically :: Prism' NestedAtomically NestedAtomically
__NestedAtomically :: Prism' SomeException    NestedAtomically

_NestedAtomically :: Prism' t () Source #

There is no additional information carried in a NestedAtomically Exception.

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

Instances

Instances details
AsNestedAtomically NestedAtomically Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NestedAtomically :: Prism' NestedAtomically NestedAtomically Source #

_NestedAtomically :: Prism' NestedAtomically () Source #

AsNestedAtomically SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NestedAtomically :: Prism' SomeException NestedAtomically Source #

_NestedAtomically :: Prism' SomeException () Source #

pattern NestedAtomically__ :: AsNestedAtomically s => NestedAtomically -> s Source #

Blocked Indefinitely

on MVar

class AsBlockedIndefinitelyOnMVar t where Source #

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

Minimal complete definition

__BlockedIndefinitelyOnMVar

Methods

__BlockedIndefinitelyOnMVar :: Prism' t BlockedIndefinitelyOnMVar Source #

__BlockedIndefinitelyOnMVar :: Prism' BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar
__BlockedIndefinitelyOnMVar :: Prism' SomeException             BlockedIndefinitelyOnMVar

_BlockedIndefinitelyOnMVar :: Prism' t () Source #

There is no additional information carried in a BlockedIndefinitelyOnMVar Exception.

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

Instances

Instances details
AsBlockedIndefinitelyOnMVar SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__BlockedIndefinitelyOnMVar :: Prism' SomeException BlockedIndefinitelyOnMVar Source #

_BlockedIndefinitelyOnMVar :: Prism' SomeException () Source #

AsBlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__BlockedIndefinitelyOnMVar :: Prism' BlockedIndefinitelyOnMVar BlockedIndefinitelyOnMVar Source #

_BlockedIndefinitelyOnMVar :: Prism' BlockedIndefinitelyOnMVar () Source #

pattern BlockedIndefinitelyOnMVar__ :: AsBlockedIndefinitelyOnMVar s => BlockedIndefinitelyOnMVar -> s Source #

on STM

class AsBlockedIndefinitelyOnSTM t where Source #

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.

Minimal complete definition

__BlockedIndefinitelyOnSTM

Methods

__BlockedIndefinitelyOnSTM :: Prism' t BlockedIndefinitelyOnSTM Source #

__BlockedIndefinitelyOnSTM :: Prism' BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM
__BlockedIndefinitelyOnSTM :: Prism' SomeException            BlockedIndefinitelyOnSTM

_BlockedIndefinitelyOnSTM :: Prism' t () Source #

There is no additional information carried in a BlockedIndefinitelyOnSTM Exception.

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

Instances

Instances details
AsBlockedIndefinitelyOnSTM SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__BlockedIndefinitelyOnSTM :: Prism' SomeException BlockedIndefinitelyOnSTM Source #

_BlockedIndefinitelyOnSTM :: Prism' SomeException () Source #

AsBlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__BlockedIndefinitelyOnSTM :: Prism' BlockedIndefinitelyOnSTM BlockedIndefinitelyOnSTM Source #

_BlockedIndefinitelyOnSTM :: Prism' BlockedIndefinitelyOnSTM () Source #

pattern BlockedIndefinitelyOnSTM__ :: AsBlockedIndefinitelyOnSTM s => BlockedIndefinitelyOnSTM -> s Source #

Deadlock

class AsDeadlock t where Source #

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

Minimal complete definition

__Deadlock

Methods

__Deadlock :: Prism' t Deadlock Source #

__Deadlock :: Prism' Deadlock      Deadlock
__Deadlock :: Prism' SomeException Deadlock

_Deadlock :: Prism' t () Source #

There is no information carried in a Deadlock Exception.

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

Instances

Instances details
AsDeadlock SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__Deadlock :: Prism' SomeException Deadlock Source #

_Deadlock :: Prism' SomeException () Source #

AsDeadlock Deadlock Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__Deadlock :: Prism' Deadlock Deadlock Source #

_Deadlock :: Prism' Deadlock () Source #

pattern Deadlock__ :: AsDeadlock s => Deadlock -> s Source #

pattern Deadlock_ :: AsDeadlock s => s Source #

No Such Method

class AsNoMethodError t where Source #

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

Minimal complete definition

__NoMethodError

Methods

__NoMethodError :: Prism' t NoMethodError Source #

__NoMethodError :: Prism' NoMethodError NoMethodError
__NoMethodError :: Prism' SomeException NoMethodError

_NoMethodError :: Prism' t String Source #

Extract a description of the missing method.

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

Instances

Instances details
AsNoMethodError NoMethodError Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NoMethodError :: Prism' NoMethodError NoMethodError Source #

_NoMethodError :: Prism' NoMethodError String Source #

AsNoMethodError SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__NoMethodError :: Prism' SomeException NoMethodError Source #

_NoMethodError :: Prism' SomeException String Source #

pattern NoMethodError__ :: AsNoMethodError s => NoMethodError -> s Source #

pattern NoMethodError_ :: AsNoMethodError s => String -> s Source #

Pattern Match Failure

class AsPatternMatchFail t where Source #

A pattern match failed.

Minimal complete definition

__PatternMatchFail

Methods

__PatternMatchFail :: Prism' t PatternMatchFail Source #

__PatternMatchFail :: Prism' PatternMatchFail PatternMatchFail
__PatternMatchFail :: Prism' SomeException    PatternMatchFail

_PatternMatchFail :: Prism' t String Source #

Information about the source location of the pattern.

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

Instances

Instances details
AsPatternMatchFail PatternMatchFail Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__PatternMatchFail :: Prism' PatternMatchFail PatternMatchFail Source #

_PatternMatchFail :: Prism' PatternMatchFail String Source #

AsPatternMatchFail SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__PatternMatchFail :: Prism' SomeException PatternMatchFail Source #

_PatternMatchFail :: Prism' SomeException String Source #

pattern PatternMatchFail__ :: AsPatternMatchFail s => PatternMatchFail -> s Source #

pattern PatternMatchFail_ :: AsPatternMatchFail s => String -> s Source #

Record

class AsRecConError t where Source #

An uninitialised record field was used.

Minimal complete definition

__RecConError

Methods

__RecConError :: Prism' t RecConError Source #

__RecConError :: Prism' RecConError   RecConError
__RecConError :: Prism' SomeException RecConError

_RecConError :: Prism' t String Source #

Information about the source location where the record was constructed.

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

Instances

Instances details
AsRecConError RecConError Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecConError :: Prism' RecConError RecConError Source #

_RecConError :: Prism' RecConError String Source #

AsRecConError SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecConError :: Prism' SomeException RecConError Source #

_RecConError :: Prism' SomeException String Source #

class AsRecSelError t where Source #

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.

Minimal complete definition

__RecSelError

Methods

__RecSelError :: Prism' t RecSelError Source #

__RecSelError :: Prism' RecSelError   RecSelError
__RecSelError :: Prism' SomeException RecSelError

_RecSelError :: Prism' t String Source #

Information about the source location where the record selection occurred.

_RecSelError :: Prism' RecSelError   String
_RecSelError :: Prism' SomeException String

Instances

Instances details
AsRecSelError RecSelError Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecSelError :: Prism' RecSelError RecSelError Source #

_RecSelError :: Prism' RecSelError String Source #

AsRecSelError SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecSelError :: Prism' SomeException RecSelError Source #

_RecSelError :: Prism' SomeException String Source #

class AsRecUpdError t where Source #

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.

Minimal complete definition

__RecUpdError

Methods

__RecUpdError :: Prism' t RecUpdError Source #

__RecUpdError :: Prism' RecUpdError   RecUpdError
__RecUpdError :: Prism' SomeException RecUpdError

_RecUpdError :: Prism' t String Source #

Information about the source location where the record was updated.

_RecUpdError :: Prism' RecUpdError   String
_RecUpdError :: Prism' SomeException String

Instances

Instances details
AsRecUpdError RecUpdError Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecUpdError :: Prism' RecUpdError RecUpdError Source #

_RecUpdError :: Prism' RecUpdError String Source #

AsRecUpdError SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__RecUpdError :: Prism' SomeException RecUpdError Source #

_RecUpdError :: Prism' SomeException String Source #

pattern RecConError__ :: AsRecConError s => RecConError -> s Source #

pattern RecConError_ :: AsRecConError s => String -> s Source #

pattern RecSelError__ :: AsRecSelError s => RecSelError -> s Source #

pattern RecSelError_ :: AsRecSelError s => String -> s Source #

pattern RecUpdError__ :: AsRecUpdError s => RecUpdError -> s Source #

pattern RecUpdError_ :: AsRecUpdError s => String -> s Source #

Error Call

class AsErrorCall t where Source #

This is thrown when the user calls error.

Minimal complete definition

__ErrorCall

Methods

__ErrorCall :: Prism' t ErrorCall Source #

__ErrorCall :: Prism' ErrorCall     ErrorCall
__ErrorCall :: Prism' SomeException ErrorCall

_ErrorCall :: Prism' t String Source #

Retrieve the argument given to error.

ErrorCall is isomorphic to a String.

>>> catching _ErrorCall (error "touch down!") return
"touch down!"
_ErrorCall :: Prism' ErrorCall     String
_ErrorCall :: Prism' SomeException String

Instances

Instances details
AsErrorCall ErrorCall Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__ErrorCall :: Prism' ErrorCall ErrorCall Source #

_ErrorCall :: Prism' ErrorCall String Source #

AsErrorCall SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__ErrorCall :: Prism' SomeException ErrorCall Source #

_ErrorCall :: Prism' SomeException String Source #

pattern ErrorCall__ :: AsErrorCall s => ErrorCall -> s Source #

pattern ErrorCall_ :: AsErrorCall s => String -> s Source #

Allocation Limit Exceeded

class AsAllocationLimitExceeded t where Source #

This thread has exceeded its allocation limit.

Minimal complete definition

__AllocationLimitExceeded

Methods

__AllocationLimitExceeded :: Prism' t AllocationLimitExceeded Source #

__AllocationLimitExceeded :: Prism' AllocationLimitExceeded AllocationLimitExceeded
__AllocationLimitExceeded :: Prism' SomeException           AllocationLimitExceeded

_AllocationLimitExceeded :: Prism' t () Source #

There is no additional information carried in an AllocationLimitExceeded Exception.

_AllocationLimitExceeded :: Prism' AllocationLimitExceeded ()
_AllocationLimitExceeded :: Prism' SomeException           ()

Instances

Instances details
AsAllocationLimitExceeded SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__AllocationLimitExceeded :: Prism' SomeException AllocationLimitExceeded Source #

_AllocationLimitExceeded :: Prism' SomeException () Source #

AsAllocationLimitExceeded AllocationLimitExceeded Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__AllocationLimitExceeded :: Prism' AllocationLimitExceeded AllocationLimitExceeded Source #

_AllocationLimitExceeded :: Prism' AllocationLimitExceeded () Source #

pattern AllocationLimitExceeded__ :: AsAllocationLimitExceeded s => AllocationLimitExceeded -> s Source #

Type Error

class AsTypeError t where Source #

An expression that didn't typecheck during compile time was called. This is only possible with -fdefer-type-errors.

Minimal complete definition

__TypeError

Methods

__TypeError :: Prism' t TypeError Source #

__TypeError :: Prism' TypeError     TypeError
__TypeError :: Prism' SomeException TypeError

_TypeError :: Prism' t String Source #

Details about the failed type check.

_TypeError :: Prism' TypeError     String
_TypeError :: Prism' SomeException String

Instances

Instances details
AsTypeError TypeError Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__TypeError :: Prism' TypeError TypeError Source #

_TypeError :: Prism' TypeError String Source #

AsTypeError SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__TypeError :: Prism' SomeException TypeError Source #

_TypeError :: Prism' SomeException String Source #

pattern TypeError__ :: AsTypeError s => TypeError -> s Source #

pattern TypeError_ :: AsTypeError s => String -> s Source #

Compaction Failed

class AsCompactionFailed t where Source #

Compaction found an object that cannot be compacted. Functions cannot be compacted, nor can mutable objects or pinned objects.

Minimal complete definition

__CompactionFailed

Methods

__CompactionFailed :: Prism' t CompactionFailed Source #

__CompactionFailed :: Prism' CompactionFailed CompactionFailed
__CompactionFailed :: Prism' SomeException    CompactionFailed

_CompactionFailed :: Prism' t String Source #

Information about why a compaction failed.

_CompactionFailed :: Prism' CompactionFailed String
_CompactionFailed :: Prism' SomeException    String

Instances

Instances details
AsCompactionFailed SomeException Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__CompactionFailed :: Prism' SomeException CompactionFailed Source #

_CompactionFailed :: Prism' SomeException String Source #

AsCompactionFailed CompactionFailed Source # 
Instance details

Defined in Control.Exception.Lens

Methods

__CompactionFailed :: Prism' CompactionFailed CompactionFailed Source #

_CompactionFailed :: Prism' CompactionFailed String Source #

pattern CompactionFailed__ :: AsCompactionFailed s => CompactionFailed -> s Source #

pattern CompactionFailed_ :: AsCompactionFailed s => String -> s Source #

Handling Exceptions

class AsHandlingException t where Source #

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

Minimal complete definition

__HandlingException