exceptional-0.2.0.0: Essentially the Maybe type with error messages.

Safe HaskellSafe-Inferred
LanguageHaskell98

Control.Exceptional

Synopsis

Documentation

data Exceptional x Source

This is basically specialized 'Either String', or Maybe with error messages.

Constructors

Failure String 
Success x 

Instances

Alternative Exceptional 
Monad Exceptional

This is fail-safe, so to speak. That is,

fail = Failure
Functor Exceptional 
Applicative Exceptional 
Eq x => Eq (Exceptional x) 
Read x => Read (Exceptional x) 
Show x => Show (Exceptional x) 

runExceptional :: Monad m => Exceptional x -> m x Source

Convert Exceptional into another Monad. If you don't have proper exception handling in your monad, this can throw errors.

runExceptional (Failure s) = fail s
runExceptional (Success s) = pure s

fromMaybe :: String -> Maybe a -> Exceptional a Source

Convert a Maybe to an Exceptional

fromMaybe s Nothing = fail s
fromMaybe s (Just x) = pure x

toMaybe :: Exceptional a -> Maybe a Source

Convert an Exceptional into a Maybe. This function disregards the error message.

toMaybe (Success x) = Just x
toMaybe (Failure _) = Nothing

fromEither :: Either String a -> Exceptional a Source

Convert an Either String to an Exceptional

fromEither (Left s) = fail s
fromEither (Right x) = pure x

toEither :: Exceptional a -> Either String a Source

Convert an Exceptional to an Either String

toEither (Failure s) = Left s
toEither (Success x) = Right x

exceptIO :: IO a -> IO (Exceptional a) Source

A wrapper around tryIOError. Encapsulates I/O exceptions in the Exceptional monad.

exceptional :: MonadCatch m => m a -> m (Exceptional a) Source

Run an exception-prone action in another monad, catch the errors in Exceptional.

failures :: Foldable t => t (Exceptional x) -> [String] Source

Get all of the Failures from a bunch of Exceptionals

successes :: Foldable t => t (Exceptional x) -> [x] Source

Get all of the Successes from a bunch of Exceptionals

foldExceptional :: Foldable t => t (Exceptional x) -> Either [String] [x] Source

Given a number of Exceptional values:

  • If all are Successful, then return Right with the sucesses * If there is at least one Failure, then return Left the list of error messages