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

Control.Monad.Exception.Asynchronous

Contents

Description

Asynchronous exceptions can occur during the construction of a lazy data structure. They are represent by a lazy data structure itself.

TODO:

  • Check whether laziness behaviour is reasonable.

Synopsis

Plain monad

data Exceptional e a Source

Contains a value and a reason why the computation of the value of type a was terminated. Imagine a as a list type, and an according operation like the readFile operation. If the exception part is Nothing then the value could be constructed regularly. If the exception part is Just then the value could not be constructed completely. However you can read the result of type a lazily, even if an exception occurs while it is evaluated. If you evaluate the exception part, then the result value is certainly computed completely.

However, we cannot provide functions that combine several Exceptional values, due to the very different ways of combining the results of type a. It is recommended to process the result value in an application specific way, and after consumption of the result, throw a synchronous exception using toSynchronous.

Constructors

Exceptional 

Fields

exception :: Maybe e
 
result :: a
 

Instances

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

pure :: a -> Exceptional e aSource

Create an exceptional value without exception.

broken :: e -> a -> Exceptional e aSource

Create an exceptional value with exception.

manySynchronousTSource

Arguments

:: Monad m 
=> (m (Exceptional e b) -> m (Exceptional e b))

defer function

-> (a -> b -> b)

cons function

-> b
empty
-> ExceptionalT e m a

atomic action to repeat

-> m (Exceptional e b) 

Repeat an action with synchronous exceptions until an exception occurs. Combine all atomic results using the bind function. It may be cons = (:) and empty = [] for b being a list type. The defer function may be id or unsafeInterleaveIO for lazy read operations. The exception is returned as asynchronous exception.

processToSynchronousT_Source

Arguments

:: Monad m 
=> (b -> Maybe (a, b))

decons function

-> (a -> ExceptionalT e m ())

action that is run for each element fetched from x

-> Exceptional e b

value x of type b with asynchronous exception

-> ExceptionalT e m () 

Scan x using the decons function and run an action with synchronous exceptions for each element fetched from x. Each invocation of an element action may stop this function due to an exception. If all element action can be performed successfully and if there is an asynchronous exception then at the end this exception is raised as synchronous exception. decons function might be viewL.

handling of special result types

zipWith :: (a -> b -> c) -> Exceptional e [a] -> Exceptional e [b] -> Exceptional e [c]Source

This is an example for application specific handling of result values. Assume you obtain two lazy lists say from readFile and you want to zip their contents. If one of the stream readers emits an exception, we quit with that exception. If both streams have throw an exception at the same file position, the exception of the first stream is propagated.

append :: Monoid a => Exceptional e a -> Exceptional e a -> Exceptional e aSource

This is an example for application specific handling of result values. Assume you obtain two lazy lists say from readFile and you want to append their contents. If the first stream ends with an exception, this exception is kept and the second stream is not touched. If the first stream can be read successfully, the second one is appended until stops.

force :: Exceptional e a -> Exceptional e aSource

construct Exceptional constructor lazily

traverse :: Applicative f => (a -> f b) -> Exceptional e a -> f (Exceptional e b)Source

mapM :: Monad m => (a -> m b) -> Exceptional e a -> m (Exceptional e b)Source

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