errors-1.4.0: Simplified error-handling

Safe HaskellNone

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 is 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

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

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

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