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 | Haskell2010 |
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
- 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
- throwing_ :: AReview SomeException () -> m x
- 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 a => a -> SomeException
- class Handleable e (m :: Type -> Type) (h :: Type -> Type) | 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
- pattern AssertionFailed__ :: AsAssertionFailed s => AssertionFailed -> s
- 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 NonTermination
- _NonTermination :: Prism' t ()
- pattern NonTermination__ :: AsNonTermination s => NonTermination -> s
- pattern NonTermination_ :: AsNonTermination s => s
- class AsNestedAtomically t where
- __NestedAtomically :: Prism' t NestedAtomically
- _NestedAtomically :: Prism' t ()
- pattern NestedAtomically__ :: AsNestedAtomically s => NestedAtomically -> s
- pattern NestedAtomically_ :: AsNestedAtomically s => s
- class AsBlockedIndefinitelyOnMVar t where
- pattern BlockedIndefinitelyOnMVar__ :: AsBlockedIndefinitelyOnMVar s => BlockedIndefinitelyOnMVar -> s
- pattern BlockedIndefinitelyOnMVar_ :: AsBlockedIndefinitelyOnMVar s => s
- class AsBlockedIndefinitelyOnSTM t where
- pattern BlockedIndefinitelyOnSTM__ :: AsBlockedIndefinitelyOnSTM s => BlockedIndefinitelyOnSTM -> s
- pattern BlockedIndefinitelyOnSTM_ :: AsBlockedIndefinitelyOnSTM s => s
- class AsDeadlock t where
- __Deadlock :: Prism' t Deadlock
- _Deadlock :: Prism' t ()
- pattern Deadlock__ :: AsDeadlock s => Deadlock -> s
- pattern Deadlock_ :: AsDeadlock s => s
- class AsNoMethodError t where
- pattern NoMethodError__ :: AsNoMethodError s => NoMethodError -> s
- pattern NoMethodError_ :: AsNoMethodError s => String -> s
- class AsPatternMatchFail t where
- pattern PatternMatchFail__ :: AsPatternMatchFail s => PatternMatchFail -> s
- pattern PatternMatchFail_ :: AsPatternMatchFail s => String -> s
- class AsRecConError t where
- __RecConError :: Prism' t RecConError
- _RecConError :: Prism' t String
- class AsRecSelError t where
- __RecSelError :: Prism' t RecSelError
- _RecSelError :: Prism' t String
- class AsRecUpdError t where
- __RecUpdError :: Prism' t RecUpdError
- _RecUpdError :: Prism' t String
- pattern RecConError__ :: AsRecConError s => RecConError -> s
- pattern RecConError_ :: AsRecConError s => String -> s
- pattern RecSelError__ :: AsRecSelError s => RecSelError -> s
- pattern RecSelError_ :: AsRecSelError s => String -> s
- pattern RecUpdError__ :: AsRecUpdError s => RecUpdError -> s
- pattern RecUpdError_ :: AsRecUpdError s => String -> s
- class AsErrorCall t where
- __ErrorCall :: Prism' t ErrorCall
- _ErrorCall :: Prism' t String
- pattern ErrorCall__ :: AsErrorCall s => ErrorCall -> s
- pattern ErrorCall_ :: AsErrorCall s => String -> s
- class AsAllocationLimitExceeded t where
- pattern AllocationLimitExceeded__ :: AsAllocationLimitExceeded s => AllocationLimitExceeded -> s
- pattern AllocationLimitExceeded_ :: AsAllocationLimitExceeded s => s
- class AsTypeError t where
- __TypeError :: Prism' t TypeError
- _TypeError :: Prism' t String
- pattern TypeError__ :: AsTypeError s => TypeError -> s
- pattern TypeError_ :: AsTypeError s => String -> s
- class AsCompactionFailed t where
- pattern CompactionFailed__ :: AsCompactionFailed s => CompactionFailed -> s
- pattern CompactionFailed_ :: AsCompactionFailed s => String -> s
- class AsHandlingException t where
- pattern HandlingException__ :: AsHandlingException s => HandlingException -> s
- 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 ReifiedPrism
(or any ReifiedFold
, really).
>>>
catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching
::MonadCatch
m =>Prism'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Lens'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>Iso'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatch
m =>ReifiedFold
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 ReifiedPrism
(or any ReifiedGetter
), discarding
the information about the match. This is particularly useful when you have
a
where the result of the Prism'
e ()ReifiedPrism
or ReifiedFold
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 rcatching_
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatch
m =>ReifiedFold
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 rhandling
::MonadCatch
m =>Lens'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatch
m =>Traversal'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatch
m =>Iso'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatch
m =>ReifiedFold
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatch
m =>ReifiedGetter
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 rhandling_
::MonadCatch
m =>Lens'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatch
m =>Traversal'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatch
m =>Iso'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatch
m =>ReifiedGetter
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatch
m =>ReifiedFold
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 ReifiedPrism
(or any ReifiedFold
) 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 =>ReifiedGetter
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatch
m =>ReifiedFold
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 =>ReifiedGetter
SomeException
a -> m r -> m (Maybe r)trying_
::MonadCatch
m =>ReifiedFold
SomeException
a -> m r -> m (Maybe r)
Throwing
throwing :: AReview SomeException b -> b -> r Source #
Throw an Exception
described by a ReifiedPrism
. Exceptions may be thrown from
purely functional code, but may only be caught within the IO
Monad
.
throwing
l ≡reviews
lthrow
throwing
::Prism'
SomeException
t -> t -> rthrowing
::Iso'
SomeException
t -> t -> r
throwing_ :: AReview SomeException () -> m x 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 ReifiedPrism
.
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
ethrowingM
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
lthrow
throwingM
::MonadThrow
m =>Prism'
SomeException
t -> t -> m rthrowingM
::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 ReifiedPrism
in the target thread.
throwingTo
thread l ≡reviews
l (throwTo
thread)
throwingTo
::ThreadId
->Prism'
SomeException
t -> t -> m athrowingTo
::ThreadId
->Iso'
SomeException
t -> t -> m a
Mapping
mappedException :: (Exception e, Exception e') => Setter s s e e' Source #
This ReifiedSetter
can be used to purely map over the Exception
s 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 Exception
s 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
-> fSomeException
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.
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
::Getter
SomeException
a -> (a ->IO
r) ->Handler
rhandler
::Fold
SomeException
a -> (a ->IO
r) ->Handler
rhandler
::Prism'
SomeException
a -> (a ->IO
r) ->Handler
rhandler
::Lens'
SomeException
a -> (a ->IO
r) ->Handler
rhandler
::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 rhandler
::Fold
SomeException
a -> (a -> m r) ->Handler
m rhandler
::Prism'
SomeException
a -> (a -> m r) ->Handler
m rhandler
::Lens'
SomeException
a -> (a -> m r) ->Handler
m rhandler
::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 rhandler
::Fold
e a -> (a -> m r) ->Handler
e m rhandler
::Prism'
e a -> (a -> m r) ->Handler
e m rhandler
::Lens'
e a -> (a -> m r) ->Handler
e m rhandler
::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
rhandler_
::Fold
SomeException
a ->IO
r ->Handler
rhandler_
::Prism'
SomeException
a ->IO
r ->Handler
rhandler_
::Lens'
SomeException
a ->IO
r ->Handler
rhandler_
::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 rhandler_
::Fold
SomeException
a -> m r ->Handler
m rhandler_
::Prism'
SomeException
a -> m r ->Handler
m rhandler_
::Lens'
SomeException
a -> m r ->Handler
m rhandler_
::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 rhandler_
::Fold
e a -> m r ->Handler
e m rhandler_
::Prism'
e a -> m r ->Handler
e m rhandler_
::Lens'
e a -> m r ->Handler
e m rhandler_
::Traversal'
e a -> m r ->Handler
e 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.
_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
pattern IOException_ :: AsIOException s => IOException -> s Source #
Arithmetic Exceptions
_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
_RatioZeroDenominator :: AsArithException t => Prism' t () Source #
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.
_ArrayException :: Prism' t ArrayException Source #
Extract information about an ArrayException
.
_ArrayException
::Prism'
ArrayException
ArrayException
_ArrayException
::Prism'
SomeException
ArrayException
Instances
_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 #
__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
pattern AssertionFailed__ :: AsAssertionFailed s => AssertionFailed -> s Source #
pattern AssertionFailed_ :: AsAssertionFailed s => String -> s Source #
Async Exceptions
class AsAsyncException t where Source #
Asynchronous exceptions.
_AsyncException :: Prism' t AsyncException Source #
There are several types of AsyncException
.
_AsyncException
::Equality'
AsyncException
AsyncException
_AsyncException
::Prism'
SomeException
AsyncException
Instances
_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 #
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.
__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
pattern NonTermination__ :: AsNonTermination s => NonTermination -> s Source #
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.
__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
()
pattern NestedAtomically__ :: AsNestedAtomically s => NestedAtomically -> s Source #
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.
__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
()
pattern BlockedIndefinitelyOnMVar__ :: AsBlockedIndefinitelyOnMVar s => BlockedIndefinitelyOnMVar -> s Source #
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.
__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
()
pattern BlockedIndefinitelyOnSTM__ :: AsBlockedIndefinitelyOnSTM s => BlockedIndefinitelyOnSTM -> s Source #
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.
__Deadlock :: Prism' t Deadlock Source #
Instances
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.
__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
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.
__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
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.
__RecConError :: Prism' t RecConError Source #
_RecConError :: Prism' t String Source #
Information about the source location where the record was constructed.
_RecConError
::Prism'
RecConError
String
_RecConError
::Prism'
SomeException
String
Instances
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.
__RecSelError :: Prism' t RecSelError Source #
_RecSelError :: Prism' t String Source #
Information about the source location where the record selection occurred.
_RecSelError
::Prism'
RecSelError
String
_RecSelError
::Prism'
SomeException
String
Instances
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.
__RecUpdError :: Prism' t RecUpdError Source #
_RecUpdError :: Prism' t String Source #
Information about the source location where the record was updated.
_RecUpdError
::Prism'
RecUpdError
String
_RecUpdError
::Prism'
SomeException
String
Instances
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
.
__ErrorCall :: Prism' t ErrorCall Source #
_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
AsErrorCall ErrorCall Source # | |
Defined in Control.Exception.Lens | |
AsErrorCall SomeException Source # | |
Defined in Control.Exception.Lens |
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.
__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
()
pattern AllocationLimitExceeded__ :: AsAllocationLimitExceeded s => AllocationLimitExceeded -> s Source #
pattern AllocationLimitExceeded_ :: AsAllocationLimitExceeded s => 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
.
__TypeError :: Prism' t TypeError Source #
_TypeError :: Prism' t String Source #
Details about the failed type check.
_TypeError
::Prism'
TypeError
String
_TypeError
::Prism'
SomeException
String
Instances
AsTypeError TypeError Source # | |
Defined in Control.Exception.Lens | |
AsTypeError SomeException Source # | |
Defined in Control.Exception.Lens |
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.
__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
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
.
__HandlingException :: Prism' t HandlingException Source #
__HandlingException
::Prism'
HandlingException
HandlingException
__HandlingException
::Prism'
SomeException
HandlingException
_HandlingException :: Prism' t () Source #
There is no information carried in a HandlingException
.
_HandlingException
::Prism'
HandlingException
()_HandlingException
::Prism'
SomeException
()
pattern HandlingException__ :: AsHandlingException s => HandlingException -> s Source #
pattern HandlingException_ :: AsHandlingException s => s Source #