| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Control.Monad.Error.Hoist
Contents
Description
This module provides helper functions for lifting partiality types into
error-carrying monads like ExceptT.
For example, consider the following App monad that may throw BadPacket
errors:
data AppError = BadPacketTextnewtype App a = App (EitherTAppErrorIO) a deriving (Functor,Applicative,Monad,MonadErrorAppError,MonadIO)
We may have an existing function that attempts to parse a ByteString:
parsePacket ::ByteString->EitherTextPacket
We can lift this error into the App monad using (:<%?>)
appParsePacket ::ByteString->AppPacket appParsePacket s = parsePacket s <%?> BadPacket
Instances also exist for extracting errors from other partiality types
like and Either e.ExceptT e m
Synopsis
- hoistError :: (PluckError e t m, MonadError e' m) => (e -> e') -> t a -> m a
- hoistErrorM :: (PluckError e t m, MonadError e' m) => (e -> e') -> m (t a) -> m a
- (<%?>) :: (PluckError e t m, MonadError e' m) => t a -> (e -> e') -> m a
- (<%!?>) :: (PluckError e t m, MonadError e' m) => m (t a) -> (e -> e') -> m a
- (<?>) :: (PluckError e t m, MonadError e' m) => t a -> e' -> m a
- (<!?>) :: (PluckError e t m, MonadError e' m) => m (t a) -> e' -> m a
- class PluckError e t m | t -> e where
- pluckError :: t a -> m (Either e a)
- foldError :: (e -> m r) -> (a -> m r) -> t a -> m r
Documentation
hoistError :: (PluckError e t m, MonadError e' m) => (e -> e') -> t a -> m a Source #
Given a conversion from the error in t a to e', we can hoist the
computation into m.
hoistError::MonadErrore m -> (() -> e) ->Maybea -> m ahoistError::MonadErrore m -> (a -> e) ->Eithera b -> m bhoistError::MonadErrore m -> (a -> e) ->ExceptTa m b -> m b
hoistErrorM :: (PluckError e t m, MonadError e' m) => (e -> e') -> m (t a) -> m a Source #
A version of hoistError that operates on values already in the monad.
hoistErrorM::MonadErrore m => (() -> e) -> m (Maybea) -> m ahoistErrorM::MonadErrore m => (a -> e) -> m (Eithera b) -> m bhoistErrorM::MonadErrore m => (a -> e) ->ExceptTa m b ->ExceptTa m b
Operators
The operators in this package are named according to a scheme:
(is the simplest error-handling function: it replaces any error with its second argument.<?>)- The additional
!in(and<!?>)(means the operator handles values that are already "in a monad".<%!?>) - The additional
%in(and<%?>)(means the operator takes a function argument, which it applies to the error from the partiality type. (The mnemonic is that<%!?>)%sometimes means "mod", and we abuse "mod" as a shorthand for "modify". It's a long bow, butlensuses the same mnemonic.)
(<%?>) :: (PluckError e t m, MonadError e' m) => t a -> (e -> e') -> m a infixl 8 Source #
A flipped synonym for hoistError.
(<%?>) ::MonadErrore m =>Maybea -> (() -> e) -> m a (<%?>) ::MonadErrore m =>Eithera b -> (a -> e) -> m b (<%?>) ::MonadErrore m =>ExceptTa m b -> (a -> e) ->ExceptTa m b
(<%!?>) :: (PluckError e t m, MonadError e' m) => m (t a) -> (e -> e') -> m a infixl 8 Source #
A flipped synonym for hoistErrorM.
(<%!?>) ::MonadErrore m => m (Maybea) -> (() -> e) -> m a (<%!?>) ::MonadErrore m => m (Eithera b) -> (a -> e) -> m b (<%!?>) ::MonadErrore m =>ExceptTa m b -> (a -> e) ->ExceptTa m b
(<?>) :: (PluckError e t m, MonadError e' m) => t a -> e' -> m a infixl 8 Source #
A version of <%?> that ignores the error in t a and replaces it
with a new one.
(<?>) ::MonadErrore m =>Maybea -> e -> m a (<?>) ::MonadErrore m =>Eithera b -> e -> m b (<?>) ::MonadErrore m =>ExceptTa m b -> e ->ExceptTa m b
(<!?>) :: (PluckError e t m, MonadError e' m) => m (t a) -> e' -> m a infixl 8 Source #
A version of <?> that operates on values already in the monad.
(<!?>) ::MonadErrore m => m (Maybea) -> e -> m a (<!?>) ::MonadErrore m => m (Eithera b) -> e -> m b (<!?>) ::MonadErrore m =>ExceptTa m b -> e ->ExceptTa m b
Helper class
class PluckError e t m | t -> e where Source #
A class for plucking an error e out of a partiality type t.
Minimal complete definition
Methods
pluckError :: t a -> m (Either e a) Source #
default pluckError :: Applicative m => t a -> m (Either e a) Source #
foldError :: (e -> m r) -> (a -> m r) -> t a -> m r Source #
Instances
| (Applicative m, e ~ ()) => PluckError e Maybe m Source # | |
Defined in Control.Monad.Error.Hoist | |
| Applicative m => PluckError e (Either e) m Source # | |
Defined in Control.Monad.Error.Hoist | |
| Monad m => PluckError e (ExceptT e m) m Source # | |
Defined in Control.Monad.Error.Hoist | |