Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module exports miscellaneous error-handling functions.
- hush :: Either a b -> Maybe b
- hushT :: Monad m => ExceptT a m b -> MaybeT m b
- note :: a -> Maybe b -> Either a b
- noteT :: Monad m => a -> MaybeT m b -> ExceptT a m b
- hoistMaybe :: Monad m => Maybe b -> MaybeT m b
- hoistEither :: Monad m => Either e a -> ExceptT e m a
- (??) :: Applicative m => Maybe a -> e -> ExceptT e m a
- (!?) :: Applicative m => m (Maybe a) -> e -> ExceptT e m a
- failWith :: Applicative m => e -> Maybe a -> ExceptT e m a
- failWithM :: Applicative m => e -> m (Maybe a) -> ExceptT 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 => ExceptT a m b -> m Bool
- isRightT :: Monad m => ExceptT a m b -> m Bool
- fmapRT :: Monad m => (a -> b) -> ExceptT l m a -> ExceptT l m b
- exceptT :: Monad m => (a -> m c) -> (b -> m c) -> ExceptT a m b -> m c
- bimapExceptT :: Functor m => (e -> f) -> (a -> b) -> ExceptT e m a -> ExceptT f m b
- err :: String -> IO ()
- errLn :: String -> IO ()
- tryIO :: MonadIO m => IO a -> ExceptT IOException m a
- syncIO :: Unexceptional m => IO a -> ExceptT SomeException m a
Conversion
(??) :: Applicative m => Maybe a -> e -> ExceptT e m a Source
(!?) :: Applicative m => m (Maybe a) -> e -> ExceptT e m a Source
failWith :: Applicative m => e -> Maybe a -> ExceptT e m a Source
failWithM :: Applicative m => e -> m (Maybe a) -> ExceptT e m a Source
Bool
Maybe
MaybeT
Either
ExceptT
exceptT :: Monad m => (a -> m c) -> (b -> m c) -> ExceptT a m b -> m c Source
Fold an ExceptT
by providing one continuation for each constructor
bimapExceptT :: Functor m => (e -> f) -> (a -> b) -> ExceptT e m a -> ExceptT f m b Source
Transform the left and right value
Error Reporting
Exceptions
tryIO :: MonadIO m => IO a -> ExceptT IOException m a Source
Catch IOException
s and convert them to the ExceptT
monad
syncIO :: Unexceptional m => IO a -> ExceptT SomeException m a Source
Catch all exceptions, except for asynchronous exceptions found in base
and convert them to the ExceptT
monad