explicit-exception-0.1: Exceptions which are explicit in the type signature.

Control.Monad.Exception.Synchronous

Contents

Description

Synchronous exceptions immediately abort a series of computations. We provide monads for describing this behaviour.

Synopsis

Plain monad

data Exceptional e a Source

Like Either, but explicitly intended for handling of exceptional results. In contrast to Either we do not support fail. Calling fail in the Exceptional monad is an error. This way, we do not require that an exception can be derived from a String, yet, we require no constraint on the exception type at all.

Constructors

Success a 
Exception e 

Instances

getExceptionNull :: Exceptional e () -> Maybe eSource

useful in connection with Control.Monad.Exception.Asynchronous.continue

force :: Exceptional e a -> Exceptional e aSource

If you are sure that the value is always a Success you can tell that the run-time system thus making your program lazy. However, try to avoid this function by using catch and friends, since this function is partial.

mapException :: (e0 -> e1) -> Exceptional e0 a -> Exceptional e1 aSource

mapExceptional :: (e0 -> e1) -> (a -> b) -> Exceptional e0 a -> Exceptional e1 bSource

catch :: Exceptional e0 a -> (e0 -> Exceptional e1 a) -> Exceptional e1 aSource

resolve :: (e -> a) -> Exceptional e a -> aSource

Monad transformer

newtype ExceptionalT e m a Source

like ErrorT, but ExceptionalT is the better name in order to distinguish from real (programming) errors

Constructors

ExceptionalT 

Fields

runExceptionalT :: m (Exceptional e a)
 

Instances

MonadTrans (ExceptionalT e) 
Monad m => Monad (ExceptionalT e m) 
Functor m => Functor (ExceptionalT e m) 
MonadFix m => MonadFix (ExceptionalT e m) 
Applicative m => Applicative (ExceptionalT e m) 
(MonadSIO m, ContainsIOException e) => MonadIO (ExceptionalT e m) 

fromErrorT :: Monad m => ErrorT e m a -> ExceptionalT e m aSource

toErrorT :: Monad m => ExceptionalT e m a -> ErrorT e m aSource

fromEitherT :: Monad m => m (Either e a) -> ExceptionalT e m aSource

toEitherT :: Monad m => ExceptionalT e m a -> m (Either e a)Source

forceT :: Monad m => ExceptionalT e m a -> ExceptionalT e m aSource

see force

mapExceptionT :: Monad m => (e0 -> e1) -> ExceptionalT e0 m a -> ExceptionalT e1 m aSource

mapExceptionalT :: (m (Exceptional e0 a) -> n (Exceptional e1 b)) -> ExceptionalT e0 m a -> ExceptionalT e1 n bSource

throwT :: Monad m => e -> ExceptionalT e m aSource

catchT :: Monad m => ExceptionalT e0 m a -> (e0 -> ExceptionalT e1 m a) -> ExceptionalT e1 m aSource

bracketT :: Monad m => ExceptionalT e m h -> (h -> ExceptionalT e m ()) -> (h -> ExceptionalT e m a) -> ExceptionalT e m aSource

If the enclosed monad has custom exception facilities, they could skip the cleanup code. Make sure, that this cannot happen by choosing an appropriate monad.

resolveT :: Monad m => (e -> m a) -> ExceptionalT e m a -> m aSource

tryT :: Monad m => ExceptionalT e m a -> m (Exceptional e a)Source

manyTSource

Arguments

:: Monad m 
=> (e0 -> Maybe e1)

exception handler

-> (a -> b -> b)

cons function

-> b
empty
-> ExceptionalT e0 m a

atomic action to repeat

-> ExceptionalT e1 m b 

Repeat an action until an exception occurs. Initialize the result with empty and add new elements using cons (e.g. [] and (:)). The exception handler decides whether the terminating exception is re-raised (Just) or catched (Nothing).