errors-1.4.6: Simplified error-handling

Safe HaskellSafe-Inferred

Control.Error.Util

Contents

Description

This module exports miscellaneous error-handling functions.

Synopsis

Conversion

Use these functions to convert between Maybe, Either, MaybeT, and EitherT.

Note that hoistEither and eitherT are provided by the either package.

hush :: Either a b -> Maybe bSource

Suppress the Left value of an Either

hushT :: Monad m => EitherT a m b -> MaybeT m bSource

Suppress the Left value of an EitherT

note :: a -> Maybe b -> Either a bSource

Tag the Nothing value of a Maybe

noteT :: Monad m => a -> MaybeT m b -> EitherT a m bSource

Tag the Nothing value of a MaybeT

hoistMaybe :: Monad m => Maybe b -> MaybeT m bSource

Lift a Maybe to the MaybeT monad

(??) :: Applicative m => Maybe a -> e -> EitherT e m aSource

Convert a Maybe value into the EitherT monad

(!?) :: Applicative m => m (Maybe a) -> e -> EitherT e m aSource

Convert an applicative Maybe value into the EitherT monad

failWith :: Applicative m => e -> Maybe a -> EitherT e m aSource

Convert a Maybe value into the EitherT monad

Named version of (??) with arguments flipped

failWithM :: Applicative m => e -> m (Maybe a) -> EitherT e m aSource

Convert an applicative Maybe value into the EitherT monad

Named version of (!?) with arguments flipped

Bool

bool :: a -> a -> Bool -> aSource

Case analysis for the Bool type.

 bool a b c == if c then b else a

Maybe

(?:) :: Maybe a -> a -> aSource

An infix form of fromMaybe with arguments flipped.

MaybeT

maybeT :: Monad m => m b -> (a -> m b) -> MaybeT m a -> m bSource

Case analysis for MaybeT

Use the first argument if the MaybeT computation fails, otherwise apply the function to the successful result.

just :: Monad m => a -> MaybeT m aSource

Analogous to Just and equivalent to return

nothing :: Monad m => MaybeT m aSource

Analogous to Nothing and equivalent to mzero

isJustT :: Monad m => MaybeT m a -> m BoolSource

Analogous to isJust, but for MaybeT

isNothingT :: Monad m => MaybeT m a -> m BoolSource

Analogous to isNothing, but for MaybeT

Either

isLeft :: Either a b -> BoolSource

Returns whether argument is a Left

isRight :: Either a b -> BoolSource

Returns whether argument is a Right

fmapR :: (a -> b) -> Either l a -> Either l bSource

fmap specialized to Either, given a name symmetric to fmapL

newtype AllE e r Source

Run multiple Either computations and succeed if all of them succeed

mappends all successes or failures

Constructors

AllE 

Fields

runAllE :: Either e r
 

Instances

(Monoid e, Monoid r) => Monoid (AllE e r) 

newtype AnyE e r Source

Run multiple Either computations and succeed if any of them succeed

mappends all successes or failures

Constructors

AnyE 

Fields

runAnyE :: Either e r
 

Instances

(Monoid e, Monoid r) => Monoid (AnyE e r) 

EitherT

isLeftT :: Monad m => EitherT a m b -> m BoolSource

Analogous to isLeft, but for EitherT

isRightT :: Monad m => EitherT a m b -> m BoolSource

Analogous to isRight, but for EitherT

fmapRT :: Monad m => (a -> b) -> EitherT l m a -> EitherT l m bSource

fmap specialized to EitherT, given a name symmetric to fmapLT

Error Reporting

err :: String -> IO ()Source

Write a string to standard error

errLn :: String -> IO ()Source

Write a string with a newline to standard error

Exceptions

tryIO :: MonadIO m => IO a -> EitherT IOException m aSource

Catch IOExceptions and convert them to the EitherT monad

syncIO :: MonadIO m => IO a -> EitherT SomeException m aSource

Catch all exceptions, except for asynchronous exceptions found in base and convert them to the EitherT monad