Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
HoistError
extends MonadError
with hoistError
, which enables lifting
of partiality types such as Maybe
and
into the monad.Either
e
For example, consider the following App
monad that may throw BadPacket
errors:
data AppError = BadPacketString
newtype App a = App (EitherT
AppErrorIO
) a deriving (Functor
,Applicative
,Monad
,MonadError
AppError,MonadIO
)
We may have an existing function that parses a String
into a Maybe
Packet
parsePacket ::String
->Maybe
Packet
which can be lifted into the App
monad with hoistError
appParsePacket ::String
->App
Packet appParsePacket s =hoistError
(\() -> BadPacket "no parse") (parsePacket s)
Similar instances exist for
and Either
e
.EitherT
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
,
) into a monad. The parameter Either
ee
represents the error
information carried by the partiality type t
, and e'
represents the type
of error expected in the monad m
.
hoistError :: (e -> e') -> t α -> m α Source #
Given a conversion from the error in t α
to e'
, we can hoist the
computation into m
.
hoistError ::MonadError
e m -> (() -> e) ->Maybe
a -> m a hoistError ::MonadError
e m -> (a -> e) ->Either
a b -> m b hoistError ::MonadError
e m -> (a -> e) ->ExceptT
a m b -> m b
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
.
<%?>
::MonadError
e m =>Maybe
a -> (() -> e) -> m a<%?>
::MonadError
e m =>Either
a b -> (a -> e) -> m b<%?>
::MonadError
e m =>ExceptT
a m b -> (a -> e) ->ExceptT
a 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.
<%!?>
::MonadError
e m => m (Maybe
a) -> (() -> e) -> m a<%!?>
::MonadError
e m => m (Either
a b) -> (a -> e) -> m b<%!?>
::MonadError
e m =>ExceptT
a m b -> (a -> e) ->ExceptT
a 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'
.
<?>
::MonadError
e m =>Maybe
a -> e -> m a<?>
::MonadError
e m =>Either
a b -> e -> m b<?>
::MonadError
e m =>ExceptT
a m b -> e ->ExceptT
a 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.
<!?>
::MonadError
e m => m (Maybe
a) -> e -> m a<!?>
::MonadError
e m => m (Either
a b) -> e -> m b<!?>
::MonadError
e m =>ExceptT
a m b -> e ->ExceptT
a m b