error-or-0.1.1.0: Composable, hierarchical errors.
Safe HaskellNone
LanguageHaskell2010

Data.ErrorOr

Description

Provides composable and hierarchical errors, with pretty printing. The errors are accumulated in a tree like structure, ErrorAcc. ErrorAcc is disigned to be read by humans, via pretty, not dispatched on by code. Using toE to convert an ErrorOr to IO throws (in case it holds an error) a PrettyErrAcc that uses pretty in the show instance.

Synopsis

Documentation

newtype ErrorOr a Source #

Use Applicative's sequenceA and sequenceA_ to compose ErrorOrs as opposed to Monad derived functions like sequence.

Constructors

ErrorOr 

Instances

Instances details
Monad ErrorOr Source #

OrError's instances for Monad and Applicative don't align, but the Monad and MonadFail instances are too useful (as in convenient) to pass on. In particular, composing two failing actions using the Applicative instance creates a composite error, where as composing the same two actions using the Monad instance (>>) produces only the error from the first action in the sequence. This is a consequence of the fact that for Monads executing the second of two actions ((>>) is defined in terms of (>>=)) requires the result from the first to be passed to the second: the very result that is not available if the first action fails!

Instance details

Defined in Data.ErrorOr

Methods

(>>=) :: ErrorOr a -> (a -> ErrorOr b) -> ErrorOr b #

(>>) :: ErrorOr a -> ErrorOr b -> ErrorOr b #

return :: a -> ErrorOr a #

Functor ErrorOr Source # 
Instance details

Defined in Data.ErrorOr

Methods

fmap :: (a -> b) -> ErrorOr a -> ErrorOr b #

(<$) :: a -> ErrorOr b -> ErrorOr a #

MonadFail ErrorOr Source # 
Instance details

Defined in Data.ErrorOr

Methods

fail :: String -> ErrorOr a #

Applicative ErrorOr Source # 
Instance details

Defined in Data.ErrorOr

Methods

pure :: a -> ErrorOr a #

(<*>) :: ErrorOr (a -> b) -> ErrorOr a -> ErrorOr b #

liftA2 :: (a -> b -> c) -> ErrorOr a -> ErrorOr b -> ErrorOr c #

(*>) :: ErrorOr a -> ErrorOr b -> ErrorOr b #

(<*) :: ErrorOr a -> ErrorOr b -> ErrorOr a #

Foldable ErrorOr Source # 
Instance details

Defined in Data.ErrorOr

Methods

fold :: Monoid m => ErrorOr m -> m #

foldMap :: Monoid m => (a -> m) -> ErrorOr a -> m #

foldMap' :: Monoid m => (a -> m) -> ErrorOr a -> m #

foldr :: (a -> b -> b) -> b -> ErrorOr a -> b #

foldr' :: (a -> b -> b) -> b -> ErrorOr a -> b #

foldl :: (b -> a -> b) -> b -> ErrorOr a -> b #

foldl' :: (b -> a -> b) -> b -> ErrorOr a -> b #

foldr1 :: (a -> a -> a) -> ErrorOr a -> a #

foldl1 :: (a -> a -> a) -> ErrorOr a -> a #

toList :: ErrorOr a -> [a] #

null :: ErrorOr a -> Bool #

length :: ErrorOr a -> Int #

elem :: Eq a => a -> ErrorOr a -> Bool #

maximum :: Ord a => ErrorOr a -> a #

minimum :: Ord a => ErrorOr a -> a #

sum :: Num a => ErrorOr a -> a #

product :: Num a => ErrorOr a -> a #

Traversable ErrorOr Source # 
Instance details

Defined in Data.ErrorOr

Methods

traverse :: Applicative f => (a -> f b) -> ErrorOr a -> f (ErrorOr b) #

sequenceA :: Applicative f => ErrorOr (f a) -> f (ErrorOr a) #

mapM :: Monad m => (a -> m b) -> ErrorOr a -> m (ErrorOr b) #

sequence :: Monad m => ErrorOr (m a) -> m (ErrorOr a) #

ErrorConv Maybe ErrorOr Source #

Convert from 'Maybe a' to 'ErrorOr a'. It converts Nothing simply to an error with msg Nothing.

Instance details

Defined in Data.ErrorOr

Methods

toE :: Maybe a -> ErrorOr a Source #

ErrorConv ErrorOr IO Source #

Convert from ErrorOr to IO. toE throws a PrettyErrAcc if the input holds an error.

Instance details

Defined in Data.ErrorOr

Methods

toE :: ErrorOr a -> IO a Source #

Eq a => Eq (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Methods

(==) :: ErrorOr a -> ErrorOr a -> Bool #

(/=) :: ErrorOr a -> ErrorOr a -> Bool #

Ord a => Ord (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Methods

compare :: ErrorOr a -> ErrorOr a -> Ordering #

(<) :: ErrorOr a -> ErrorOr a -> Bool #

(<=) :: ErrorOr a -> ErrorOr a -> Bool #

(>) :: ErrorOr a -> ErrorOr a -> Bool #

(>=) :: ErrorOr a -> ErrorOr a -> Bool #

max :: ErrorOr a -> ErrorOr a -> ErrorOr a #

min :: ErrorOr a -> ErrorOr a -> ErrorOr a #

Read a => Read (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Show a => Show (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Methods

showsPrec :: Int -> ErrorOr a -> ShowS #

show :: ErrorOr a -> String #

showList :: [ErrorOr a] -> ShowS #

Semigroup a => Semigroup (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Methods

(<>) :: ErrorOr a -> ErrorOr a -> ErrorOr a #

sconcat :: NonEmpty (ErrorOr a) -> ErrorOr a #

stimes :: Integral b => b -> ErrorOr a -> ErrorOr a #

(Semigroup (ErrorOr a), Monoid a) => Monoid (ErrorOr a) Source # 
Instance details

Defined in Data.ErrorOr

Methods

mempty :: ErrorOr a #

mappend :: ErrorOr a -> ErrorOr a -> ErrorOr a #

mconcat :: [ErrorOr a] -> ErrorOr a #

err :: Text -> ErrorOr a Source #

Produce an error.

tag :: Text -> ErrorOr a -> ErrorOr a Source #

Annotate the error with context information.

pattern Error :: ErrorAcc -> ErrorOr a Source #

pattern OK :: a -> ErrorOr a Source #

fromOK :: ErrorOr a -> a Source #

A partial function, like fromRight.

class ErrorConv t s where Source #

Convert between functors that hold error info.

Methods

toE :: t a -> s a Source #

Instances

Instances details
ErrorConv Maybe ErrorOr Source #

Convert from 'Maybe a' to 'ErrorOr a'. It converts Nothing simply to an error with msg Nothing.

Instance details

Defined in Data.ErrorOr

Methods

toE :: Maybe a -> ErrorOr a Source #

ErrorConv ErrorOr IO Source #

Convert from ErrorOr to IO. toE throws a PrettyErrAcc if the input holds an error.

Instance details

Defined in Data.ErrorOr

Methods

toE :: ErrorOr a -> IO a Source #

data ErrorAcc Source #

Instances

Instances details
Eq ErrorAcc Source # 
Instance details

Defined in Data.ErrorOr

Ord ErrorAcc Source # 
Instance details

Defined in Data.ErrorOr

Read ErrorAcc Source # 
Instance details

Defined in Data.ErrorOr

Show ErrorAcc Source # 
Instance details

Defined in Data.ErrorOr

Semigroup ErrorAcc Source # 
Instance details

Defined in Data.ErrorOr

pretty Source #

Arguments

:: Int

Initial indent, usually 0

-> ErrorAcc 
-> Text 

Pretty print the error.

newtype PrettyErrAcc Source #

A wrapper over ErrorAcc to provide human readable exceptions. (Exception class' displayException does not seem to be used by GHC) https://stackoverflow.com/questions/55490766/why-doesn-t-ghc-use-my-displayexception-method

Constructors

PrettyErrAcc 

tagIO :: Text -> IO a -> IO a Source #

Tag an exception with an annotation.

It acts on two types of exceptions: IOException and PrettyErrAcc. For PrettyErrAcc it is streightforward tagging. For IOException, otoh, it converts the error message into Text via String and turns it into PrettyErrAcc tagged with provided adnotation.

This is rather a convenience function. Sometimes it is convenient to fail "msg" in IO, and tag it higher up with some context. The need for tagIO often comes with lookup (from error-or-utils package) when used from IO, which is overloaded for MonadFail.

Since ver 0.1.1.0