errors-2.3.0: Simplified error-handling

Safe HaskellSafe
LanguageHaskell98

Control.Error.Util

Contents

Description

This module exports miscellaneous error-handling functions.

Synopsis

Conversion

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

hush :: Either a b -> Maybe b Source #

Suppress the Left value of an Either

hushT :: Monad m => ExceptT a m b -> MaybeT m b Source #

Suppress the Left value of an ExceptT

note :: a -> Maybe b -> Either a b Source #

Tag the Nothing value of a Maybe

noteT :: Monad m => a -> MaybeT m b -> ExceptT a m b Source #

Tag the Nothing value of a MaybeT

hoistMaybe :: Monad m => Maybe b -> MaybeT m b Source #

Lift a Maybe to the MaybeT monad

hoistEither :: Monad m => Either e a -> ExceptT e m a Source #

Upgrade an Either to an ExceptT

(??) :: Applicative m => Maybe a -> e -> ExceptT e m a Source #

Convert a Maybe value into the ExceptT monad

(!?) :: Applicative m => m (Maybe a) -> e -> ExceptT e m a Source #

Convert an applicative Maybe value into the ExceptT monad

failWith :: Applicative m => e -> Maybe a -> ExceptT e m a Source #

Convert a Maybe value into the ExceptT monad

Named version of (??) with arguments flipped

failWithM :: Applicative m => e -> m (Maybe a) -> ExceptT e m a Source #

Convert an applicative Maybe value into the ExceptT monad

Named version of (!?) with arguments flipped

Bool

bool :: a -> a -> Bool -> a Source #

Case analysis for the Bool type.

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

Maybe

(?:) :: Maybe a -> a -> a infixr 0 Source #

An infix form of fromMaybe with arguments flipped.

MaybeT

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

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 a Source #

Analogous to Just and equivalent to return

nothing :: Monad m => MaybeT m a Source #

Analogous to Nothing and equivalent to mzero

isJustT :: Monad m => MaybeT m a -> m Bool Source #

Analogous to isJust, but for MaybeT

isNothingT :: Monad m => MaybeT m a -> m Bool Source #

Analogous to isNothing, but for MaybeT

Either

isLeft :: Either a b -> Bool Source #

Returns whether argument is a Left

isRight :: Either a b -> Bool Source #

Returns whether argument is a Right

fmapR :: (a -> b) -> Either l a -> Either l b Source #

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

Instances

(Semigroup e, Semigroup r) => Semigroup (AllE e r) Source # 

Methods

(<>) :: AllE e r -> AllE e r -> AllE e r #

sconcat :: NonEmpty (AllE e r) -> AllE e r #

stimes :: Integral b => b -> AllE e r -> AllE e r #

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

Methods

mempty :: AllE e r #

mappend :: AllE e r -> AllE e r -> AllE e r #

mconcat :: [AllE e r] -> 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

Instances

(Semigroup e, Semigroup r) => Semigroup (AnyE e r) Source # 

Methods

(<>) :: AnyE e r -> AnyE e r -> AnyE e r #

sconcat :: NonEmpty (AnyE e r) -> AnyE e r #

stimes :: Integral b => b -> AnyE e r -> AnyE e r #

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

Methods

mempty :: AnyE e r #

mappend :: AnyE e r -> AnyE e r -> AnyE e r #

mconcat :: [AnyE e r] -> AnyE e r #

ExceptT

isLeftT :: Monad m => ExceptT a m b -> m Bool Source #

Analogous to isLeft, but for ExceptT

isRightT :: Monad m => ExceptT a m b -> m Bool Source #

Analogous to isRight, but for ExceptT

fmapRT :: Monad m => (a -> b) -> ExceptT l m a -> ExceptT l m b Source #

fmap specialized to ExceptT, given a name symmetric to fmapLT

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

err :: Text -> IO () Source #

Write a string to standard error

errLn :: Text -> IO () Source #

Write a string with a newline to standard error

Exceptions

tryIO :: MonadIO m => IO a -> ExceptT IOException m a Source #

Catch IOExceptions and convert them to the ExceptT monad

handleExceptT :: (Exception e, Functor m, MonadCatch m) => (e -> x) -> m a -> ExceptT x m a Source #

Run a monad action which may throw an exception in the ExceptT monad

syncIO :: MonadIO 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