Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- throwM :: forall e m a. (Exception e, MonadThrow m, HasCallStack) => e -> m a
- throwString :: forall m a. (MonadThrow m, HasCallStack) => String -> m a
- fromJustNoteM :: forall m a. (MonadThrow m, HasCallStack) => String -> Maybe a -> m a
- impossible :: forall m a. (MonadThrow m, HasCallStack) => m a
- catch :: forall e m a. (Exception e, MonadCatch m, HasCallStack) => m a -> (e -> m a) -> m a
- catchJust :: forall e b m a. (Exception e, MonadCatch m, HasCallStack) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
- catches :: forall m a. (MonadCatch m, HasCallStack) => m a -> [ExceptionHandler m a] -> m a
- try :: forall e m a. (Exception e, MonadCatch m, HasCallStack) => m a -> m (Either e a)
- tryJust :: forall e b m a. (Exception e, MonadCatch m, HasCallStack) => (e -> Maybe b) -> m a -> m (Either b a)
- withException :: forall e a m b. (Exception e, MonadCatch m, HasCallStack) => m a -> (e -> m b) -> m a
- checkpoint :: (HasCallStack, MonadCatch m) => Annotation -> m a -> m a
- checkpointMany :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a
- checkpointCallStack :: forall m a. (MonadCatch m, HasCallStack) => m a -> m a
- class Monad m => MonadThrow (m :: Type -> Type)
- class MonadThrow m => MonadCatch (m :: Type -> Type)
- class MonadCatch m => MonadMask (m :: Type -> Type)
- module Freckle.App.Exception.Types
Documentation
throwM :: forall e m a. (Exception e, MonadThrow m, HasCallStack) => e -> m a Source #
throwString :: forall m a. (MonadThrow m, HasCallStack) => String -> m a Source #
fromJustNoteM :: forall m a. (MonadThrow m, HasCallStack) => String -> Maybe a -> m a Source #
impossible :: forall m a. (MonadThrow m, HasCallStack) => m a Source #
catch :: forall e m a. (Exception e, MonadCatch m, HasCallStack) => m a -> (e -> m a) -> m a Source #
catchJust :: forall e b m a. (Exception e, MonadCatch m, HasCallStack) => (e -> Maybe b) -> m a -> (b -> m a) -> m a Source #
:: forall m a. (MonadCatch m, HasCallStack) | |
=> m a | Action to run |
-> [ExceptionHandler m a] | Recovery actions to run if the first action throws an exception
with a type of either |
-> m a |
:: forall e m a. (Exception e, MonadCatch m, HasCallStack) | |
=> m a | Action to run |
-> m (Either e a) | Returns |
:: forall e b m a. (Exception e, MonadCatch m, HasCallStack) | |
=> (e -> Maybe b) | |
-> m a | Action to run |
-> m (Either b a) |
withException :: forall e a m b. (Exception e, MonadCatch m, HasCallStack) => m a -> (e -> m b) -> m a Source #
checkpoint :: (HasCallStack, MonadCatch m) => Annotation -> m a -> m a #
Add a single Annotation
to any exceptions thrown in the following
action. The CallStack
present on any AnnotatedException
will also be
updated to include this location.
Example:
main = do checkpoint "Foo" $ do print =<< readFile "I don't exist.markdown"
The exception thrown due to a missing file will now have an Annotation
Foo
.
Since: annotated-exception-0.1.0.0
checkpointMany :: (MonadCatch m, HasCallStack) => [Annotation] -> m a -> m a #
Add the list of Annotation
to any exception thrown in the following
action.
Since: annotated-exception-0.1.0.0
:: forall m a. (MonadCatch m, HasCallStack) | |
=> m a | Action that might throw whatever types of exceptions |
-> m a | Action that only throws |
When dealing with a library that does not use AnnotatedException
,
apply this function to augment its exceptions with call stacks.
Miscellany
class Monad m => MonadThrow (m :: Type -> Type) #
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
Instances
class MonadThrow m => MonadCatch (m :: Type -> Type) #
A class for monads which allow exceptions to be caught, in particular
exceptions which were thrown by throwM
.
Instances should obey the following law:
catch (throwM e) f = f e
Note that the ability to catch an exception does not guarantee that we can
deal with all possible exit points from a computation. Some monads, such as
continuation-based stacks, allow for more than just a success/failure
strategy, and therefore catch
cannot be used by those monads to properly
implement a function such as finally
. For more information, see
MonadMask
.
Instances
class MonadCatch m => MonadMask (m :: Type -> Type) #
A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.
Instances should ensure that, in the following code:
fg = f `finally` g
The action g
is called regardless of what occurs within f
, including
async exceptions. Some monads allow f
to abort the computation via other
effects than throwing an exception. For simplicity, we will consider aborting
and throwing an exception to be two forms of "throwing an error".
If f
and g
both throw an error, the error thrown by fg
depends on which
errors we're talking about. In a monad transformer stack, the deeper layers
override the effects of the inner layers; for example, ExceptT e1 (Except
e2) a
represents a value of type Either e2 (Either e1 a)
, so throwing both
an e1
and an e2
will result in Left e2
. If f
and g
both throw an
error from the same layer, instances should ensure that the error from g
wins.
Effects other than throwing an error are also overridden by the deeper layers.
For example, StateT s Maybe a
represents a value of type s -> Maybe (a,
s)
, so if an error thrown from f
causes this function to return Nothing
,
any changes to the state which f
also performed will be erased. As a
result, g
will see the state as it was before f
. Once g
completes,
f
's error will be rethrown, so g
' state changes will be erased as well.
This is the normal interaction between effects in a monad transformer stack.
By contrast, lifted-base's
version of finally
always discards all of g
's non-IO effects, and g
never sees any of f
's non-IO effects, regardless of the layer ordering and
regardless of whether f
throws an error. This is not the result of
interacting effects, but a consequence of MonadBaseControl
's approach.
Instances
module Freckle.App.Exception.Types