| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Error.Hoist
Description
HoistError extends MonadError with hoistError, which enables lifting
 of partiality types such as Maybe and Either e
For example, consider the following App monad that may throw BadPacket
 errors:
data AppError = BadPacketStringnewtype App a = App (EitherTAppErrorIO) a deriving (Functor,Applicative,Monad,MonadErrorAppError,MonadIO)
We may have an existing function that parses a String into a Maybe Packet
parsePacket ::String->MaybePacket
which can be lifted into the App monad with hoistError
appParsePacket ::String->AppPacket appParsePacket s =hoistError(\() -> BadPacket "no parse") (parsePacket s)
Similar instances exist for Either eEitherT e m
- class Monad m => HoistError m t e e' | t -> e where
- (<%?>) :: HoistError m t e e' => t α -> (e -> e') -> m α
- (<%!?>) :: HoistError m t e e' => m (t α) -> (e -> e') -> m α
- (<?>) :: HoistError m t e e' => t α -> e' -> m α
- (<!?>) :: HoistError m t e e' => m (t α) -> e' -> m α
Documentation
class Monad m => HoistError m t e e' | t -> e where Source #
A tricky class for easily hoisting errors out of partiality types (e.g.
 Maybe, Either ee represents the error
 information carried by the partiality type t, and e' represents the type
 of error expected in the monad m.
Minimal complete definition
Methods
hoistError :: (e -> e') -> t α -> m α Source #
Given a conversion from the error in t α to e', we can hoist the
 computation into m.
hoistError ::MonadErrore m -> (() -> e) ->Maybea -> m a hoistError ::MonadErrore m -> (a -> e) ->Eithera b -> m b hoistError ::MonadErrore m -> (a -> e) ->ExceptTa m b -> m b
Instances
| MonadError e m => HoistError m Maybe () e Source # | |
| MonadError e' m => HoistError m (Either e) e e' Source # | |
| MonadError e' m => HoistError m (ErrorT e m) e e' Source # | |
(<%?>) :: HoistError m t e e' => t α -> (e -> e') -> m α 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
(<%!?>) :: HoistError m t e e' => m (t α) -> (e -> e') -> m α 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) -> (a -> e) -> m b<%!?>::MonadErrore m =>ExceptTa m b -> (a -> e) ->ExceptTa m b
(<?>) :: HoistError m t e e' => t α -> e' -> m α infixl 8 Source #
A version of hoistError that ignores the error in t α and replaces it
 with a new one in e'.
<?>::MonadErrore m =>Maybea -> e -> m a<?>::MonadErrore m =>Eithera b -> e -> m b<?>::MonadErrore m =>ExceptTa m b -> e ->ExceptTa m b
(<!?>) :: HoistError m t e e' => m (t α) -> e' -> m α 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