| Copyright | (C) 2012-16 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Control.Exception | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
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.
- catching :: MonadCatch m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- catching_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r
- handling :: MonadCatch m => Getting (First a) SomeException a -> (a -> m r) -> m r -> m r
- handling_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m r -> m r
- trying :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Either a r)
- trying_ :: MonadCatch m => Getting (First a) SomeException a -> m r -> m (Maybe r)
- throwing :: AReview SomeException b -> b -> r
- throwingM :: MonadThrow m => AReview SomeException b -> b -> m r
- throwingTo :: MonadIO m => ThreadId -> AReview SomeException b -> b -> m ()
- mappedException :: (Exception e, Exception e') => Setter s s e e'
- mappedException' :: Exception e' => Setter s s SomeException e'
- exception :: Exception a => Prism' SomeException a
- pattern Exception :: () => Exception t => t -> SomeException
- class Handleable e m h | h -> e m where
- class AsIOException t where
- pattern IOException_ :: () => AsIOException s => IOException -> s
- class AsArithException t where
- _Overflow :: AsArithException t => Prism' t ()
- _Underflow :: AsArithException t => Prism' t ()
- _LossOfPrecision :: AsArithException t => Prism' t ()
- _DivideByZero :: AsArithException t => Prism' t ()
- _Denormal :: AsArithException t => Prism' t ()
- _RatioZeroDenominator :: AsArithException t => Prism' t ()
- pattern ArithException_ :: () => AsArithException s => ArithException -> s
- pattern Overflow_ :: () => AsArithException s => s
- pattern Underflow_ :: () => AsArithException s => s
- pattern LossOfPrecision_ :: () => AsArithException s => s
- pattern DivideByZero_ :: () => AsArithException s => s
- pattern Denormal_ :: () => AsArithException s => s
- pattern RatioZeroDenominator_ :: () => AsArithException s => s
- class AsArrayException t where
- _IndexOutOfBounds :: AsArrayException t => Prism' t String
- _UndefinedElement :: AsArrayException t => Prism' t String
- pattern ArrayException_ :: () => AsArrayException s => ArrayException -> s
- pattern IndexOutOfBounds_ :: () => AsArrayException s => String -> s
- pattern UndefinedElement_ :: () => AsArrayException s => String -> s
- class AsAssertionFailed t where- _AssertionFailed :: Prism' t String
 
- pattern AssertionFailed_ :: () => AsAssertionFailed s => String -> s
- class AsAsyncException t where
- _StackOverflow :: AsAsyncException t => Prism' t ()
- _HeapOverflow :: AsAsyncException t => Prism' t ()
- _ThreadKilled :: AsAsyncException t => Prism' t ()
- _UserInterrupt :: AsAsyncException t => Prism' t ()
- pattern AsyncException_ :: () => AsAsyncException s => AsyncException -> s
- pattern StackOverflow_ :: () => AsAsyncException s => s
- pattern HeapOverflow_ :: () => AsAsyncException s => s
- pattern ThreadKilled_ :: () => AsAsyncException s => s
- pattern UserInterrupt_ :: () => AsAsyncException s => s
- class AsNonTermination t where- _NonTermination :: Prism' t ()
 
- pattern NonTermination_ :: () => AsNonTermination s => s
- class AsNestedAtomically t where- _NestedAtomically :: Prism' t ()
 
- pattern NestedAtomically_ :: () => AsNestedAtomically s => s
- class AsBlockedIndefinitelyOnMVar t where- _BlockedIndefinitelyOnMVar :: Prism' t ()
 
- pattern BlockedIndefinitelyOnMVar_ :: () => AsBlockedIndefinitelyOnMVar s => s
- class AsBlockedIndefinitelyOnSTM t where- _BlockedIndefinitelyOnSTM :: Prism' t ()
 
- pattern BlockedIndefinitelyOnSTM_ :: () => AsBlockedIndefinitelyOnSTM s => s
- class AsDeadlock t where
- pattern Deadlock_ :: () => AsDeadlock s => s
- class AsNoMethodError t where- _NoMethodError :: Prism' t String
 
- pattern NoMethodError_ :: () => AsNoMethodError s => String -> s
- class AsPatternMatchFail t where
- pattern PatternMatchFail_ :: () => AsPatternMatchFail s => String -> s
- class AsRecConError t where- _RecConError :: Prism' t String
 
- class AsRecSelError t where- _RecSelError :: Prism' t String
 
- class AsRecUpdError t where- _RecUpdError :: Prism' t String
 
- pattern RecConError_ :: () => AsRecConError s => String -> s
- pattern RecSelError_ :: () => AsRecSelError s => String -> s
- pattern RecUpdError_ :: () => AsRecUpdError s => String -> s
- class AsErrorCall t where- _ErrorCall :: Prism' t String
 
- pattern ErrorCall_ :: () => AsErrorCall s => String -> s
- class AsHandlingException t where- _HandlingException :: Prism' t ()
 
- pattern HandlingException_ :: () => AsHandlingException s => s
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::MonadCatchm =>Prism'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Lens'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Traversal'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>Iso'SomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>GetterSomeExceptiona -> m r -> (a -> m r) -> m rcatching::MonadCatchm =>FoldSomeExceptiona -> 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 particuarly useful when you have
 a Prism' e ()Prism or Fold isn't
 particularly valuable, just the fact that it matches.
>>>catching_ _AssertionFailed (assert False (return "uncaught")) $ return "caught""caught"
catching_::MonadCatchm =>Prism'SomeExceptiona -> m r -> m r -> m rcatching_::MonadCatchm =>Lens'SomeExceptiona -> m r -> m r -> m rcatching_::MonadCatchm =>Traversal'SomeExceptiona -> m r -> m r -> m rcatching_::MonadCatchm =>Iso'SomeExceptiona -> m r -> m r -> m rcatching_::MonadCatchm =>GetterSomeExceptiona -> m r -> m r -> m rcatching_::MonadCatchm =>FoldSomeExceptiona -> 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::MonadCatchm =>Prism'SomeExceptiona -> (a -> m r) -> m r -> m rhandling::MonadCatchm =>Lens'SomeExceptiona -> (a -> m r) -> m r -> m rhandling::MonadCatchm =>Traversal'SomeExceptiona -> (a -> m r) -> m r -> m rhandling::MonadCatchm =>Iso'SomeExceptiona -> (a -> m r) -> m r -> m rhandling::MonadCatchm =>FoldSomeExceptiona -> (a -> m r) -> m r -> m rhandling::MonadCatchm =>GetterSomeExceptiona -> (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_::MonadCatchm =>Prism'SomeExceptiona -> m r -> m r -> m rhandling_::MonadCatchm =>Lens'SomeExceptiona -> m r -> m r -> m rhandling_::MonadCatchm =>Traversal'SomeExceptiona -> m r -> m r -> m rhandling_::MonadCatchm =>Iso'SomeExceptiona -> m r -> m r -> m rhandling_::MonadCatchm =>GetterSomeExceptiona -> m r -> m r -> m rhandling_::MonadCatchm =>FoldSomeExceptiona -> 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::MonadCatchm =>Prism'SomeExceptiona -> m r -> m (Eithera r)trying::MonadCatchm =>Lens'SomeExceptiona -> m r -> m (Eithera r)trying::MonadCatchm =>Traversal'SomeExceptiona -> m r -> m (Eithera r)trying::MonadCatchm =>Iso'SomeExceptiona -> m r -> m (Eithera r)trying::MonadCatchm =>GetterSomeExceptiona -> m r -> m (Eithera r)trying::MonadCatchm =>FoldSomeExceptiona -> m r -> m (Eithera 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_::MonadCatchm =>Prism'SomeExceptiona -> m r -> m (Maybe r)trying_::MonadCatchm =>Lens'SomeExceptiona -> m r -> m (Maybe r)trying_::MonadCatchm =>Traversal'SomeExceptiona -> m r -> m (Maybe r)trying_::MonadCatchm =>Iso'SomeExceptiona -> m r -> m (Maybe r)trying_::MonadCatchm =>GetterSomeExceptiona -> m r -> m (Maybe r)trying_::MonadCatchm =>FoldSomeExceptiona -> m r -> m (Maybe r)
Throwing
throwing :: AReview SomeException b -> b -> r Source
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:
throwingl e `seq` x ≡throwingethrowingMl 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.
throwingMl ≡reviewslthrow
throwingM::MonadThrowm =>Prism'SomeExceptiont -> t -> m rthrowingM::MonadThrowm =>Iso'SomeExceptiont -> 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.
throwingTothread l ≡reviewsl (throwTothread)
throwingTo::ThreadId->Prism'SomeExceptiont -> t -> m athrowingTo::ThreadId->Iso'SomeExceptiont -> 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:: (Applicativef,Exceptiona) => (a -> f a) ->SomeException-> fSomeException
pattern Exception :: () => Exception t => t -> SomeException Source
Exception Handlers
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 | 
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.
Minimal complete definition
Nothing
Methods
_IOException :: Prism' t IOException Source
Unfortunately the name ioException is taken by base for
 throwing IOExceptions.
_IOException::Prism'IOExceptionIOException_IOException::Prism'SomeExceptionIOException
Many combinators for working with an IOException are available
 in System.IO.Error.Lens.
pattern IOException_ :: () => AsIOException s => IOException -> s Source
Arithmetic Exceptions
class AsArithException t where Source
Arithmetic exceptions.
Minimal complete definition
Nothing
Methods
_Overflow :: AsArithException t => Prism' t () Source
Handle arithmetic _Overflow.
_Overflow≡_ArithException._Overflow
_Overflow::Prism'ArithExceptionArithException_Overflow::Prism'SomeExceptionArithException
_Underflow :: AsArithException t => Prism' t () Source
Handle arithmetic _Underflow.
_Underflow≡_ArithException._Underflow
_Underflow::Prism'ArithExceptionArithException_Underflow::Prism'SomeExceptionArithException
_LossOfPrecision :: AsArithException t => Prism' t () Source
Handle arithmetic loss of precision.
_LossOfPrecision≡_ArithException._LossOfPrecision
_LossOfPrecision::Prism'ArithExceptionArithException_LossOfPrecision::Prism'SomeExceptionArithException
_DivideByZero :: AsArithException t => Prism' t () Source
Handle division by zero.
_DivideByZero≡_ArithException._DivideByZero
_DivideByZero::Prism'ArithExceptionArithException_DivideByZero::Prism'SomeExceptionArithException
_Denormal :: AsArithException t => Prism' t () Source
Handle exceptional _Denormalized floating pure.
_Denormal≡_ArithException._Denormal
_Denormal::Prism'ArithExceptionArithException_Denormal::Prism'SomeExceptionArithException
_RatioZeroDenominator :: AsArithException t => Prism' t () Source
Added in base 4.6 in response to this libraries discussion:
http://haskell.1045720.n5.nabble.com/Data-Ratio-and-exceptions-td5711246.html
_RatioZeroDenominator≡_ArithException._RatioZeroDenominator
_RatioZeroDenominator::Prism'ArithExceptionArithException_RatioZeroDenominator::Prism'SomeExceptionArithException
pattern ArithException_ :: () => AsArithException s => ArithException -> s Source
pattern Overflow_ :: () => AsArithException s => s Source
pattern Underflow_ :: () => AsArithException s => s Source
pattern LossOfPrecision_ :: () => AsArithException s => s Source
pattern DivideByZero_ :: () => AsArithException s => s Source
pattern Denormal_ :: () => AsArithException s => s Source
pattern RatioZeroDenominator_ :: () => AsArithException s => s Source
Array Exceptions
class AsArrayException t where Source
Exceptions generated by array operations.
Minimal complete definition
Nothing
Methods
_ArrayException :: Prism' t ArrayException Source
Extract information about an ArrayException.
_ArrayException::Prism'ArrayExceptionArrayException_ArrayException::Prism'SomeExceptionArrayException
_IndexOutOfBounds :: AsArrayException t => Prism' t String Source
An attempt was made to index an array outside its declared bounds.
_IndexOutOfBounds≡_ArrayException._IndexOutOfBounds
_IndexOutOfBounds::Prism'ArrayExceptionString_IndexOutOfBounds::Prism'SomeExceptionString
_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'ArrayExceptionString_UndefinedElement::Prism'SomeExceptionString
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
Minimal complete definition
Nothing
Methods
_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'AssertionFailedString_AssertionFailed::Prism'SomeExceptionString
pattern AssertionFailed_ :: () => AsAssertionFailed s => String -> s Source
Async Exceptions
class AsAsyncException t where Source
Asynchronous exceptions.
Minimal complete definition
Nothing
Methods
_AsyncException :: Prism' t AsyncException Source
There are several types of AsyncException.
_AsyncException::Equality'AsyncExceptionAsyncException_AsyncException::Prism'SomeExceptionAsyncException
_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 HeapOverflowexceptions.
_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
pattern StackOverflow_ :: () => AsAsyncException s => s Source
pattern HeapOverflow_ :: () => AsAsyncException s => s Source
pattern ThreadKilled_ :: () => AsAsyncException s => s Source
pattern UserInterrupt_ :: () => AsAsyncException s => 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
Nothing
Methods
_NonTermination :: Prism' t () Source
There is no additional information carried in a NonTermination Exception.
_NonTermination::Prism'NonTermination()_NonTermination::Prism'SomeException()
pattern NonTermination_ :: () => AsNonTermination s => 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
Nothing
Methods
_NestedAtomically :: Prism' t () Source
There is no additional information carried in a NestedAtomically Exception.
_NestedAtomically::Prism'NestedAtomically()_NestedAtomically::Prism'SomeException()
pattern NestedAtomically_ :: () => AsNestedAtomically s => 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
Nothing
Methods
_BlockedIndefinitelyOnMVar :: Prism' t () Source
There is no additional information carried in a BlockedIndefinitelyOnMVar Exception.
_BlockedIndefinitelyOnMVar::Prism'BlockedIndefinitelyOnMVar()_BlockedIndefinitelyOnMVar::Prism'SomeException()
pattern BlockedIndefinitelyOnMVar_ :: () => AsBlockedIndefinitelyOnMVar s => 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
Nothing
Methods
_BlockedIndefinitelyOnSTM :: Prism' t () Source
There is no additional information carried in a BlockedIndefinitelyOnSTM Exception.
_BlockedIndefinitelyOnSTM::Prism'BlockedIndefinitelyOnSTM()_BlockedIndefinitelyOnSTM::Prism'SomeException()
pattern BlockedIndefinitelyOnSTM_ :: () => AsBlockedIndefinitelyOnSTM s => 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
Nothing
Methods
Instances
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
Nothing
Methods
_NoMethodError :: Prism' t String Source
Extract a description of the missing method.
_NoMethodError::Prism'NoMethodErrorString_NoMethodError::Prism'SomeExceptionString
pattern NoMethodError_ :: () => AsNoMethodError s => String -> s Source
Pattern Match Failure
class AsPatternMatchFail t where Source
A pattern match failed.
Minimal complete definition
Nothing
Methods
_PatternMatchFail :: Prism' t String Source
Information about the source location of the pattern.
_PatternMatchFail::Prism'PatternMatchFailString_PatternMatchFail::Prism'SomeExceptionString
pattern PatternMatchFail_ :: () => AsPatternMatchFail s => String -> s Source
Record
class AsRecConError t where Source
An uninitialised record field was used.
Minimal complete definition
Nothing
Methods
_RecConError :: Prism' t String Source
Information about the source location where the record was constructed.
_RecConError::Prism'RecConErrorString_RecConError::Prism'SomeExceptionString
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
Nothing
Methods
_RecSelError :: Prism' t String Source
Information about the source location where the record selection occurred.
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
Nothing
Methods
_RecUpdError :: Prism' t String Source
Information about the source location where the record was updated.
pattern RecConError_ :: () => AsRecConError s => String -> s Source
pattern RecSelError_ :: () => AsRecSelError s => String -> 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
Nothing
Methods
_ErrorCall :: Prism' t String Source
Instances
pattern ErrorCall_ :: () => AsErrorCall 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
Nothing
Methods
_HandlingException :: Prism' t () Source
There is no information carried in a HandlingException.
_HandlingException::Prism'HandlingException()_HandlingException::Prism'SomeException()
pattern HandlingException_ :: () => AsHandlingException s => s Source