Portability | Control.Exception |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
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
MonadCatchIO
instead of just IO
. This enables them to be used
more easily in Monad
transformer stacks.
- catching :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m r
- catching_ :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m r -> m r
- handling :: MonadCatchIO m => Getting (First a) SomeException a -> (a -> m r) -> m r -> m r
- handling_ :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m r -> m r
- trying :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m (Either a r)
- throwing :: AReview s SomeException a b -> b -> r
- throwingM :: MonadIO m => AReview s SomeException a b -> b -> m r
- throwingTo :: MonadIO m => ThreadId -> AReview s SomeException a b -> b -> m ()
- exception :: Exception a => Prism' SomeException a
- class Handleable e m h | h -> e m where
- class AsIOException p f t where
- _IOException :: Overloaded' p f t IOException
- class AsArithException p f t where
- _ArithException :: Overloaded' p f t ArithException
- _Overflow :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _Underflow :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _LossOfPrecision :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _DivideByZero :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _Denormal :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _RatioZeroDenominator :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- class AsArrayException p f t where
- _ArrayException :: Overloaded' p f t ArrayException
- _IndexOutOfBounds :: (AsArrayException p f t, Choice p, Applicative f) => Overloaded' p f t String
- _UndefinedElement :: (AsArrayException p f t, Choice p, Applicative f) => Overloaded' p f t String
- class AsAssertionFailed p f t where
- _AssertionFailed :: Overloaded' p f t String
- class AsAsyncException p f t where
- _AsyncException :: Overloaded' p f t AsyncException
- _StackOverflow :: (AsAsyncException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _HeapOverflow :: (AsAsyncException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _ThreadKilled :: (AsAsyncException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- _UserInterrupt :: (AsAsyncException p f t, Choice p, Applicative f) => Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsNonTermination p f t where
- _NonTermination :: Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsNestedAtomically p f t where
- _NestedAtomically :: Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsBlockedIndefinitelyOnMVar p f t where
- _BlockedIndefinitelyOnMVar :: Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsBlockedIndefinitelyOnSTM p f t where
- _BlockedIndefinitelyOnSTM :: Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsDeadlock p f t where
- _Deadlock :: Overloaded' p f t ()
- class (Profunctor p, Functor f) => AsNoMethodError p f t where
- _NoMethodError :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsPatternMatchFail p f t where
- _PatternMatchFail :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsRecConError p f t where
- _RecConError :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsRecSelError p f t where
- _RecSelError :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsRecUpdError p f t where
- _RecUpdError :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsErrorCall p f t where
- _ErrorCall :: Overloaded' p f t String
- class (Profunctor p, Functor f) => AsHandlingException p f t where
- _HandlingException :: Overloaded' p f t ()
Handling
catching :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> (a -> m r) -> m rSource
Catch exceptions that match a given Prism
(or any Getter
, really).
>>>
catching _AssertionFailed (assert False (return "uncaught")) $ \ _ -> return "caught"
"caught"
catching
::MonadCatchIO
m =>Prism'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatchIO
m =>Lens'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatchIO
m =>Traversal'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatchIO
m =>Iso'
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatchIO
m =>Getter
SomeException
a -> m r -> (a -> m r) -> m rcatching
::MonadCatchIO
m =>Fold
SomeException
a -> m r -> (a -> m r) -> m r
catching_ :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m r -> m rSource
Catch exceptions that match a given Prism
(or any Getter
), discarding
the information about the match. This is particuarly useful when you have
a
where the result of the 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_
::MonadCatchIO
m =>Prism'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatchIO
m =>Lens'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatchIO
m =>Traversal'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatchIO
m =>Iso'
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatchIO
m =>Getter
SomeException
a -> m r -> m r -> m rcatching_
::MonadCatchIO
m =>Fold
SomeException
a -> m r -> m r -> m r
handling :: MonadCatchIO m => Getting (First a) SomeException a -> (a -> m r) -> m r -> m rSource
A version of catching
with the arguments swapped around; useful in
situations where the code for the handler is shorter.
>>>
handling _NonTermination (\_ -> return "caught") $ throwIO NonTermination
"caught"
handling
::MonadCatchIO
m =>Prism'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatchIO
m =>Lens'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatchIO
m =>Traversal'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatchIO
m =>Iso'
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatchIO
m =>Fold
SomeException
a -> (a -> m r) -> m r -> m rhandling
::MonadCatchIO
m =>Getter
SomeException
a -> (a -> m r) -> m r -> m r
handling_ :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m r -> m rSource
A version of catching_
with the arguments swapped around; useful in
situations where the code for the handler is shorter.
>>>
handling_ _NonTermination (return "caught") $ throwIO NonTermination
"caught"
handling_
::MonadCatchIO
m =>Prism'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatchIO
m =>Lens'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatchIO
m =>Traversal'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatchIO
m =>Iso'
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatchIO
m =>Getter
SomeException
a -> m r -> m r -> m rhandling_
::MonadCatchIO
m =>Fold
SomeException
a -> m r -> m r -> m r
Trying
trying :: MonadCatchIO m => Getting (First a) SomeException a -> m r -> m (Either a r)Source
A variant of try
that takes a Prism
(or any Getter
) to select which
exceptions are caught (c.f. tryJust
, catchJust
). If the
Exception
does not match the predicate, it is re-thrown.
trying
::MonadCatchIO
m =>Prism'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatchIO
m =>Lens'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatchIO
m =>Traversal'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatchIO
m =>Iso'
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatchIO
m =>Getter
SomeException
a -> m r -> m (Either
a r)trying
::MonadCatchIO
m =>Fold
SomeException
a -> m r -> m (Either
a r)
Throwing
throwing :: AReview s SomeException a b -> b -> rSource
throwingM :: MonadIO m => AReview s SomeException a b -> b -> m rSource
A variant of throwing
that can only be used within the IO
Monad
(or any other MonadCatchIO
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
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 MonadCatchIO
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
::MonadIO
m =>Prism'
SomeException
t -> t -> m rthrowingM
::MonadIO
m =>Iso'
SomeException
t -> t -> m r
throwingTo :: MonadIO m => ThreadId -> AReview s SomeException a b -> b -> m ()Source
throwingTo
raises an Exception
specified by a Prism
in the target thread.
throwingTo
thread l ≡reviews
l (throwTo
thread)
throwingTo
::ThreadId
->Prism'
SomeException
t -> t -> m athrowingTo
::ThreadId
->Iso'
SomeException
t -> t -> m a
Exceptions
exception :: Exception a => Prism' SomeException aSource
Traverse the strongly typed Exception
contained in SomeException
where the type of your function matches
the desired Exception
.
exception
:: (Applicative
f,Exception
a) => (a -> f a) ->SomeException
-> fSomeException
Exception Handlers
class Handleable e m h | h -> e m whereSource
Both MonadCatchIO-transformers
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 :: Getting (First a) e a -> (a -> m r) -> h rSource
This builds a Handler
for just the targets of a given Prism
(or any Getter
, really).
catches
... [handler
_AssertionFailed
(s ->$
"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.CatchIO
:
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_ :: Getting (First a) e a -> m r -> h rSource
This builds a Handler
for just the targets of a given Prism
(or any Getter
, really).
that ignores its input and just recovers with the stated monadic action.
catches
... [handler_
_NonTermination
(return
"looped") ,handler_
_StackOverflow
(return
"overflow") ]
This works with the Handler
type provided by Control.Exception
:
handler_
::Getter
SomeException
a ->IO
r ->Handler
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.CatchIO
:
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
Handleable SomeException IO Handler | |
Handleable SomeException m (Handler m) | |
Handleable e m (Handler e m) |
IOExceptions
class AsIOException p f t whereSource
Exceptions that occur in the IO
Monad
. An IOException
records a
more specific error type, a descriptive string and maybe the handle that was
used when the error was flagged.
Due to their richer structure relative to other exceptions, these have a more carefully overloaded signature.
_IOException :: Overloaded' p f t IOExceptionSource
Unfortunately the name ioException
is taken by base
for
throwing IOExceptions.
_IOException
::Equality'
IOException
IOException
_IOException
::Prism'
SomeException
IOException
Many combinators for working with an IOException
are available
in System.IO.Error.Lens.
(Choice p, Applicative f) => AsIOException p f SomeException | |
AsIOException p f IOException |
Arithmetic Exceptions
class AsArithException p f t whereSource
Arithmetic exceptions.
(Choice p, Applicative f) => AsArithException p f SomeException | |
AsArithException p f ArithException |
_Overflow :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
Handle arithmetic _Overflow
.
_Overflow
≡_ArithException
.
_Overflow
_Overflow
::Prism'
ArithException
ArithException
_Overflow
::Prism'
SomeException
ArithException
_Underflow :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
Handle arithmetic _Underflow
.
_Underflow
≡_ArithException
.
_Underflow
_Underflow
::Prism'
ArithException
ArithException
_Underflow
::Prism'
SomeException
ArithException
_LossOfPrecision :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
Handle arithmetic loss of precision.
_LossOfPrecision
≡_ArithException
.
_LossOfPrecision
_LossOfPrecision
::Prism'
ArithException
ArithException
_LossOfPrecision
::Prism'
SomeException
ArithException
_DivideByZero :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
Handle division by zero.
_DivideByZero
≡_ArithException
.
_DivideByZero
_DivideByZero
::Prism'
ArithException
ArithException
_DivideByZero
::Prism'
SomeException
ArithException
_Denormal :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
Handle exceptional _Denormalized floating point.
_Denormal
≡_ArithException
.
_Denormal
_Denormal
::Prism'
ArithException
ArithException
_Denormal
::Prism'
SomeException
ArithException
_RatioZeroDenominator :: (AsArithException p f t, Choice p, Applicative f) => Overloaded' p f 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'
ArithException
ArithException
_RatioZeroDenominator
::Prism'
SomeException
ArithException
Array Exceptions
class AsArrayException p f t whereSource
Exceptions generated by array operations.
_ArrayException :: Overloaded' p f t ArrayExceptionSource
Extract information about an ArrayException
.
_ArrayException
::Equality'
ArrayException
ArrayException
_ArrayException
::Prism'
SomeException
ArrayException
(Choice p, Applicative f) => AsArrayException p f SomeException | |
AsArrayException p f ArrayException |
_IndexOutOfBounds :: (AsArrayException p f t, Choice p, Applicative f) => Overloaded' p f t StringSource
An attempt was made to index an array outside its declared bounds.
_IndexOutOfBounds
≡_ArrayException
.
_IndexOutOfBounds
_IndexOutOfBounds
::Prism'
ArrayException
String
_IndexOutOfBounds
::Prism'
SomeException
String
_UndefinedElement :: (AsArrayException p f t, Choice p, Applicative f) => Overloaded' p f t StringSource
An attempt was made to evaluate an element of an array that had not been initialized.
_UndefinedElement
≡_ArrayException
.
_UndefinedElement
_UndefinedElement
::Prism'
ArrayException
String
_UndefinedElement
::Prism'
SomeException
String
Assertion Failed
class AsAssertionFailed p f t whereSource
_AssertionFailed :: Overloaded' p f t StringSource
This Exception
contains provides information about what assertion failed in the String
.
>>>
handling _AssertionFailed (\ xs -> "caught" <$ guard ("<interactive>" `isInfixOf` xs) ) $ assert False (return "uncaught")
"caught"
_AssertionFailed
::Iso'
AssertionFailed
String
_AssertionFailed
::Prism'
SomeException
String
(Choice p, Applicative f) => AsAssertionFailed p f SomeException | |
(Profunctor p, Functor f) => AsAssertionFailed p f AssertionFailed |
Async Exceptions
class AsAsyncException p f t whereSource
Asynchronous exceptions.
_AsyncException :: Overloaded' p f t AsyncExceptionSource
There are several types of AsyncException
.
_AsyncException
::Equality'
AsyncException
AsyncException
_AsyncException
::Prism'
SomeException
AsyncException
(Choice p, Applicative f) => AsAsyncException p f SomeException | |
AsAsyncException p f AsyncException |
_StackOverflow :: (AsAsyncException p f t, Choice p, Applicative f) => Overloaded' p f 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 p f t, Choice p, Applicative f) => Overloaded' p f 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 p f t, Choice p, Applicative f) => Overloaded' p f 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 p f t, Choice p, Applicative f) => Overloaded' p f t ()Source
This Exception
is raised by default in the main thread of the program when
the user requests to terminate the program via the usual mechanism(s)
(e.g. Control-C in the console).
_UserInterrupt
::Prism'
AsyncException
()_UserInterrupt
::Prism'
SomeException
()
Non-Termination
class (Profunctor p, Functor f) => AsNonTermination p f t whereSource
Thrown when the runtime system detects that the computation is guaranteed not to terminate. Note that there is no guarantee that the runtime system will notice whether any given computation is guaranteed to terminate or not.
_NonTermination :: Overloaded' p f t ()Source
There is no additional information carried in a NonTermination
Exception
.
_NonTermination
::Iso'
NonTermination
()_NonTermination
::Prism'
SomeException
()
(Choice p, Applicative f) => AsNonTermination p f SomeException | |
(Profunctor p, Functor f) => AsNonTermination p f NonTermination |
Nested Atomically
class (Profunctor p, Functor f) => AsNestedAtomically p f t whereSource
Thrown when the program attempts to call atomically, from the
STM
package, inside another call to atomically.
_NestedAtomically :: Overloaded' p f t ()Source
There is no additional information carried in a NestedAtomically
Exception
.
_NestedAtomically
::Iso'
NestedAtomically
()_NestedAtomically
::Prism'
SomeException
()
(Choice p, Applicative f) => AsNestedAtomically p f SomeException | |
(Profunctor p, Functor f) => AsNestedAtomically p f NestedAtomically |
Blocked Indefinitely
on MVar
class (Profunctor p, Functor f) => AsBlockedIndefinitelyOnMVar p f t whereSource
The thread is blocked on an MVar
, but there
are no other references to the MVar
so it can't
ever continue.
_BlockedIndefinitelyOnMVar :: Overloaded' p f t ()Source
There is no additional information carried in a BlockedIndefinitelyOnMVar
Exception
.
_BlockedIndefinitelyOnMVar
::Iso'
BlockedIndefinitelyOnMVar
()_BlockedIndefinitelyOnMVar
::Prism'
SomeException
()
(Choice p, Applicative f) => AsBlockedIndefinitelyOnMVar p f SomeException | |
(Profunctor p, Functor f) => AsBlockedIndefinitelyOnMVar p f BlockedIndefinitelyOnMVar |
on STM
class (Profunctor p, Functor f) => AsBlockedIndefinitelyOnSTM p f t whereSource
The thread is waiting to retry an STM
transaction,
but there are no other references to any TVars involved, so it can't ever
continue.
_BlockedIndefinitelyOnSTM :: Overloaded' p f t ()Source
There is no additional information carried in a BlockedIndefinitelyOnSTM
Exception
.
_BlockedIndefinitelyOnSTM
::Iso'
BlockedIndefinitelyOnSTM
()_BlockedIndefinitelyOnSTM
::Prism'
SomeException
()
(Choice p, Applicative f) => AsBlockedIndefinitelyOnSTM p f SomeException | |
(Profunctor p, Functor f) => AsBlockedIndefinitelyOnSTM p f BlockedIndefinitelyOnSTM |
Deadlock
class (Profunctor p, Functor f) => AsDeadlock p f t whereSource
There are no runnable threads, so the program is deadlocked. The
Deadlock
Exception
is raised in the main thread only.
_Deadlock :: Overloaded' p f t ()Source
(Choice p, Applicative f) => AsDeadlock p f SomeException | |
(Profunctor p, Functor f) => AsDeadlock p f Deadlock |
No Such Method
class (Profunctor p, Functor f) => AsNoMethodError p f t whereSource
A class method without a definition (neither a default definition, nor a definition in the appropriate instance) was called.
_NoMethodError :: Overloaded' p f t StringSource
Extract a description of the missing method.
_NoMethodError
::Iso'
NoMethodError
String
_NoMethodError
::Prism'
SomeException
String
(Choice p, Applicative f) => AsNoMethodError p f SomeException | |
(Profunctor p, Functor f) => AsNoMethodError p f NoMethodError |
Pattern Match Failure
class (Profunctor p, Functor f) => AsPatternMatchFail p f t whereSource
A pattern match failed.
_PatternMatchFail :: Overloaded' p f t StringSource
Information about the source location of the pattern.
_PatternMatchFail
::Iso'
PatternMatchFail
String
_PatternMatchFail
::Prism'
SomeException
String
(Choice p, Applicative f) => AsPatternMatchFail p f SomeException | |
(Profunctor p, Functor f) => AsPatternMatchFail p f PatternMatchFail |
Record
class (Profunctor p, Functor f) => AsRecConError p f t whereSource
An uninitialised record field was used.
_RecConError :: Overloaded' p f t StringSource
Information about the source location where the record was constructed.
_RecConError
::Iso'
RecConError
String
_RecConError
::Prism'
SomeException
String
(Choice p, Applicative f) => AsRecConError p f SomeException | |
(Profunctor p, Functor f) => AsRecConError p f RecConError |
class (Profunctor p, Functor f) => AsRecSelError p f t whereSource
A record selector was applied to a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.
_RecSelError :: Overloaded' p f t StringSource
Information about the source location where the record selection occurred.
(Choice p, Applicative f) => AsRecSelError p f SomeException | |
(Profunctor p, Functor f) => AsRecSelError p f RecSelError |
class (Profunctor p, Functor f) => AsRecUpdError p f t whereSource
A record update was performed on a constructor without the appropriate field. This can only happen with a datatype with multiple constructors, where some fields are in one constructor but not another.
_RecUpdError :: Overloaded' p f t StringSource
Information about the source location where the record was updated.
(Choice p, Applicative f) => AsRecUpdError p f SomeException | |
(Profunctor p, Functor f) => AsRecUpdError p f RecUpdError |
Error Call
class (Profunctor p, Functor f) => AsErrorCall p f t whereSource
This is thrown when the user calls error
.
_ErrorCall :: Overloaded' p f t StringSource
(Choice p, Applicative f) => AsErrorCall p f SomeException | |
(Profunctor p, Functor f) => AsErrorCall p f ErrorCall |
Handling Exceptions
class (Profunctor p, Functor f) => AsHandlingException p f t whereSource
This Exception
is thrown by lens
when the user somehow manages to rethrow
an internal HandlingException
.
_HandlingException :: Overloaded' p f t ()Source
There is no information carried in a HandlingException
.
_HandlingException
::Iso'
HandlingException
()_HandlingException
::Prism'
SomeException
()
(Choice p, Applicative f) => AsHandlingException p f SomeException | |
(Profunctor p, Functor f) => AsHandlingException p f HandlingException |