Safe Haskell | Safe-Inferred |
---|
This module exports miscellaneous error-handling functions.
- hush :: Either a b -> Maybe b
- hushT :: Monad m => EitherT a m b -> MaybeT m b
- note :: a -> Maybe b -> Either a b
- noteT :: Monad m => a -> MaybeT m b -> EitherT a m b
- hoistMaybe :: Monad m => Maybe b -> MaybeT m b
- (??) :: Applicative m => Maybe a -> e -> EitherT e m a
- (!?) :: Applicative m => m (Maybe a) -> e -> EitherT e m a
- failWith :: Applicative m => e -> Maybe a -> EitherT e m a
- failWithM :: Applicative m => e -> m (Maybe a) -> EitherT e m a
- bool :: a -> a -> Bool -> a
- (?:) :: Maybe a -> a -> a
- maybeT :: Monad m => m b -> (a -> m b) -> MaybeT m a -> m b
- just :: Monad m => a -> MaybeT m a
- nothing :: Monad m => MaybeT m a
- isJustT :: Monad m => MaybeT m a -> m Bool
- isNothingT :: Monad m => MaybeT m a -> m Bool
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- fmapR :: (a -> b) -> Either l a -> Either l b
- newtype AllE e r = AllE {}
- newtype AnyE e r = AnyE {}
- isLeftT :: Monad m => EitherT a m b -> m Bool
- isRightT :: Monad m => EitherT a m b -> m Bool
- fmapRT :: Monad m => (a -> b) -> EitherT l m a -> EitherT l m b
- err :: String -> IO ()
- errLn :: String -> IO ()
- tryIO :: MonadIO m => IO a -> EitherT IOException m a
- syncIO :: MonadIO m => IO a -> EitherT SomeException m a
Conversion
Use these functions to convert between Maybe
, Either
, MaybeT
, and
EitherT
.
Note that hoistEither
and eitherT
are provided by the either
package.
(??) :: Applicative m => Maybe a -> e -> EitherT e m aSource
(!?) :: Applicative m => m (Maybe a) -> e -> EitherT e m aSource
failWith :: Applicative m => e -> Maybe a -> EitherT e m aSource
failWithM :: Applicative m => e -> m (Maybe a) -> EitherT e m aSource
Bool
Maybe
MaybeT
Either
EitherT
Error Reporting
Exceptions
tryIO :: MonadIO m => IO a -> EitherT IOException m aSource
Catch IOException
s and convert them to the EitherT
monad