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

Safe HaskellSafe-Inferred

Control.Monad.Exception.Synchronous

Description

Synchronous exceptions immediately abort a series of computations. We provide monads for describing this behaviour. In contrast to ErrorT from mtl or transformers package we do not pose restrictions on the exception type.

How to tell, that a function can possibly throw more than one (kind of) exception?

If you would use the exception type (Either ParserException IOError) then this is different from (Either IOError ParserException). Thus we recommned using type classes for exceptions. Then you can use one type containing all exceptions in an application, but the type signature still tells which exceptions are actually possible. Examples:

 parser :: ParserException e => ExceptionalT e ParserMonad a

 getLine :: IOException e => ExceptionalT e IO String

 fileParser :: (ParserException e, IOException e) => ExceptionalT e IO String

Unfortunately, this way you cannot remove single exceptions from the constraints by catching them. You can only remove all of them using resolve or none. For a more advanced approach, that allows removing exceptions constraints by some non-Haskell-98 type hackery, see the exception package by Joseph Iborra.

Synopsis

Documentation

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

Monad (Exceptional e) 
Functor (Exceptional e) 
Monad (Exceptional e) => MonadFix (Exceptional e)

I think it is not a good idea to use this instance, maybe we shoul remove it. It expects that the constructor is Success and the result is undefined otherwise. But if the constructor must always be Success, why using Exceptional then, at all?

Functor (Exceptional e) => Applicative (Exceptional e) 
(Eq e, Eq a) => Eq (Exceptional e a) 
(Show e, Show a) => Show (Exceptional e a) 

getExceptionNull :: Exceptional e () -> Maybe eSource

useful in connection with continue

switch :: (e -> b) -> (a -> b) -> Exceptional e a -> bSource

Counterpart to either for Either.

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

assert :: e -> Bool -> Exceptional e ()Source

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

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

merge :: Monoid e => Exceptional e (a -> b) -> Exceptional e a -> Exceptional e bSource

see mergeT

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) 
(Monad (ExceptionalT e m), MonadFix m) => MonadFix (ExceptionalT e m)

Same restrictions applies as for instance MonadFix (Exceptional e a).

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

fromMaybeT :: Monad m => e -> MaybeT m a -> ExceptionalT e m aSource

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

switchT :: Monad m => (e -> m b) -> (a -> m b) -> ExceptionalT e m a -> m bSource

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

assertT :: Monad m => e -> Bool -> ExceptionalT e m ()Source

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).

manyMonoidTSource

Arguments

:: (Monad m, Monoid a) 
=> (e0 -> Maybe e1)

exception handler

-> ExceptionalT e0 m a

atomic action to repeat

-> ExceptionalT e1 m a 

mergeT :: (Monoid e, Monad m) => ExceptionalT e m (a -> b) -> ExceptionalT e m a -> ExceptionalT e m bSource

This combines two actions similar to Applicative's *. The result action fails if one of the input action fails, but both actions are executed. E.g. consider a compiler that emits all errors that can be detected independently, but eventually aborts if there is at least one error.

The exception type e might be a list type, or an Endo type that implements a difflist.