Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- data Exceptional e a = Exceptional {}
- pure :: a -> Exceptional e a
- broken :: e -> a -> Exceptional e a
- fromSynchronous :: a -> Exceptional e a -> Exceptional e a
- fromSynchronousNull :: Exceptional e () -> Exceptional e ()
- fromSynchronousMonoid :: Monoid a => Exceptional e a -> Exceptional e a
- toSynchronous :: Exceptional e a -> Exceptional e a
- throw :: e -> Exceptional e ()
- throwMonoid :: Monoid a => e -> Exceptional e a
- eatNothing :: Exceptional (Maybe e) a -> Exceptional e a
- zipWith :: (a -> b -> c) -> Exceptional e [a] -> Exceptional e [b] -> Exceptional e [c]
- append :: Monoid a => Exceptional e a -> Exceptional e a -> Exceptional e a
- continue :: Monoid a => Maybe e -> Exceptional e a -> Exceptional e a
- maybeAbort :: Exceptional e a -> Maybe e -> Exceptional e a
- force :: Exceptional e a -> Exceptional e a
- mapException :: (e0 -> e1) -> Exceptional e0 a -> Exceptional e1 a
- mapExceptional :: (e0 -> e1) -> (a -> b) -> Exceptional e0 a -> Exceptional e1 b
- simultaneousBind :: Exceptional e a -> (a -> Exceptional e b) -> Exceptional e b
- simultaneousBindM :: Monad m => m (Exceptional e a) -> (a -> m (Exceptional e b)) -> m (Exceptional e b)
- sequenceF :: Functor f => Exceptional e (f a) -> f (Exceptional e a)
- traverse :: Applicative f => (a -> f b) -> Exceptional e a -> f (Exceptional e b)
- sequenceA :: Applicative f => Exceptional e (f a) -> f (Exceptional e a)
- mapM :: Monad m => (a -> m b) -> Exceptional e a -> m (Exceptional e b)
- sequence :: Monad m => Exceptional e (m a) -> m (Exceptional e a)
- swapToSynchronousAsynchronous :: Exceptional e0 (Exceptional e1 a) -> Exceptional e1 (Exceptional e0 a)
- swapToAsynchronousSynchronous :: Exceptional e1 (Exceptional e0 a) -> Exceptional e0 (Exceptional e1 a)
- newtype ExceptionalT e m a = ExceptionalT {
- runExceptionalT :: m (Exceptional e a)
- fromSynchronousT :: Functor m => a -> ExceptionalT e m a -> ExceptionalT e m a
- fromSynchronousMonoidT :: (Functor m, Monoid a) => ExceptionalT e m a -> ExceptionalT e m a
- forceT :: Monad m => ExceptionalT e m a -> ExceptionalT e m a
- mapExceptionT :: Monad m => (e0 -> e1) -> ExceptionalT e0 m a -> ExceptionalT e1 m a
- mapExceptionalT :: (m (Exceptional e0 a) -> n (Exceptional e1 b)) -> ExceptionalT e0 m a -> ExceptionalT e1 n b
- throwMonoidT :: (Monad m, Monoid a) => e -> ExceptionalT e m a
- eatNothingT :: Monad m => ExceptionalT (Maybe e) m a -> ExceptionalT e m a
- bindT :: (Monad m, Monoid b) => ExceptionalT e m a -> (a -> ExceptionalT e m b) -> ExceptionalT e m b
- manySynchronousT :: Monad m => (m (Exceptional e b) -> m (Exceptional e b)) -> (a -> b -> b) -> b -> ExceptionalT e m a -> m (Exceptional e b)
- manyMonoidT :: (Monad m, Monoid a) => ExceptionalT e m a -> ExceptionalT e m a
- processToSynchronousT_ :: Monad m => (b -> Maybe (a, b)) -> (a -> ExceptionalT e m ()) -> Exceptional e b -> ExceptionalT e m ()
- appendM :: (Monad m, Monoid a) => m (Exceptional e a) -> m (Exceptional e a) -> m (Exceptional e a)
- continueM :: (Monad m, Monoid a) => m (Maybe e) -> m (Exceptional e a) -> m (Exceptional e a)
Documentation
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 general Monad
functionality
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
.
Maybe in the future we provide a monad instance which considers subsequent actions as simultaneous processes on a lazy data structure.
Instances
pure :: a -> Exceptional e a Source #
Create an exceptional value without exception.
broken :: e -> a -> Exceptional e a Source #
Create an exceptional value with exception.
fromSynchronous :: a -> Exceptional e a -> Exceptional e a Source #
fromSynchronousNull :: Exceptional e () -> Exceptional e () Source #
fromSynchronousMonoid :: Monoid a => Exceptional e a -> Exceptional e a Source #
toSynchronous :: Exceptional e a -> Exceptional e a Source #
throw :: e -> Exceptional e () Source #
I think in most cases we want throwMonoid,
thus we can replace throw
by throwMonoid
.
throwMonoid :: Monoid a => e -> Exceptional e a Source #
eatNothing :: Exceptional (Maybe e) a -> Exceptional e a Source #
You might use an exception of type Maybe e
in manyMonoidT
in order to stop the loop.
After finishing the loop you will want
to turn the Nothing
exception into a success.
This is achieved by this function.
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 a infixr 1 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 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.
append
is less strict than the Monoid
method mappend
instance.
continue :: Monoid a => Maybe e -> Exceptional e a -> Exceptional e a infixr 1 Source #
maybeAbort :: Exceptional e a -> Maybe e -> Exceptional e a infixr 1 Source #
force :: Exceptional e a -> Exceptional e a Source #
construct Exceptional constructor lazily
mapException :: (e0 -> e1) -> Exceptional e0 a -> Exceptional e1 a Source #
mapExceptional :: (e0 -> e1) -> (a -> b) -> Exceptional e0 a -> Exceptional e1 b Source #
simultaneousBind :: Exceptional e a -> (a -> Exceptional e b) -> Exceptional e b infixr 1 Source #
Deprecated: Check whether this function is really what you need. It generates an unreasonable exception when the second exception is caused by the first one.
I consider both actions to process the data simultaneously through lazy evaluation. If the second one fails too, it must have encountered an exception in the data that was successfully emitted by the first action, and thus the exception of the second action is probably earlier.
We cannot check in general whether the two exception occur at the same time, e.g. the second one might occur since the first occured and left an invalid structure. In this case we should emit the first exception, not the second one. Because of this I expect that this function is not particularly useful. Otherwise it could be used as bind operation for a monad instance.
simultaneousBindM :: Monad m => m (Exceptional e a) -> (a -> m (Exceptional e b)) -> m (Exceptional e b) infixr 1 Source #
Deprecated: Check whether this function is really what you need. It generates an unreasonable exception when the second exception is caused by the first one.
sequenceF :: Functor f => Exceptional e (f a) -> f (Exceptional e a) Source #
Is there a better name?
traverse :: Applicative f => (a -> f b) -> Exceptional e a -> f (Exceptional e b) Source #
Foldable
instance would allow to strip off the exception too easily.
I like the methods of Traversable
, but Traversable
instance requires Foldable
instance.
sequenceA :: Applicative f => Exceptional e (f a) -> f (Exceptional e a) 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 #
swapToSynchronousAsynchronous :: Exceptional e0 (Exceptional e1 a) -> Exceptional e1 (Exceptional e0 a) Source #
Consider a file format consisting of a header and a data body. The header can only be used if is read completely. Its parsing might stop with an synchronous exception. The data body can also be used if it is truncated by an exceptional event. This is expressed by an asynchronous exception. A loader for this file format can thus fail by a synchronous and an asynchronous exception. Surprisingly, both orders of nesting these two kinds of exceptional actions are equally expressive. This function converts to the form where the synchronous exception is the outer one.
This is a specialisation of sequence
and friends.
swapToAsynchronousSynchronous :: Exceptional e1 (Exceptional e0 a) -> Exceptional e0 (Exceptional e1 a) Source #
newtype ExceptionalT e m a Source #
In contrast to synchronous exceptions,
the asynchronous monad transformer is not quite a monad.
You must use the Monoid
interface or bindT
instead.
ExceptionalT | |
|
Instances
Functor m => Functor (ExceptionalT e m) Source # | |
Defined in Control.Monad.Exception.Asynchronous.Strict fmap :: (a -> b) -> ExceptionalT e m a -> ExceptionalT e m b # (<$) :: a -> ExceptionalT e m b -> ExceptionalT e m a # | |
(Monad m, Monoid a) => Semigroup (ExceptionalT e m a) Source # | |
Defined in Control.Monad.Exception.Asynchronous.Strict (<>) :: ExceptionalT e m a -> ExceptionalT e m a -> ExceptionalT e m a # sconcat :: NonEmpty (ExceptionalT e m a) -> ExceptionalT e m a # stimes :: Integral b => b -> ExceptionalT e m a -> ExceptionalT e m a # | |
(Monad m, Monoid a) => Monoid (ExceptionalT e m a) Source # | |
Defined in Control.Monad.Exception.Asynchronous.Strict mempty :: ExceptionalT e m a # mappend :: ExceptionalT e m a -> ExceptionalT e m a -> ExceptionalT e m a # mconcat :: [ExceptionalT e m a] -> ExceptionalT e m a # |
fromSynchronousT :: Functor m => a -> ExceptionalT e m a -> ExceptionalT e m a Source #
fromSynchronousMonoidT :: (Functor m, Monoid a) => ExceptionalT e m a -> ExceptionalT e m a Source #
forceT :: Monad m => ExceptionalT e m a -> ExceptionalT e m a Source #
see force
mapExceptionT :: Monad m => (e0 -> e1) -> ExceptionalT e0 m a -> ExceptionalT e1 m a Source #
mapExceptionalT :: (m (Exceptional e0 a) -> n (Exceptional e1 b)) -> ExceptionalT e0 m a -> ExceptionalT e1 n b Source #
throwMonoidT :: (Monad m, Monoid a) => e -> ExceptionalT e m a Source #
eatNothingT :: Monad m => ExceptionalT (Maybe e) m a -> ExceptionalT e m a Source #
bindT :: (Monad m, Monoid b) => ExceptionalT e m a -> (a -> ExceptionalT e m b) -> ExceptionalT e m b infixl 1 Source #
:: Monad m | |
=> (m (Exceptional e b) -> m (Exceptional e b)) |
|
-> (a -> b -> b) |
|
-> b | empty |
-> ExceptionalT e m a | atomic action to repeat |
-> m (Exceptional e b) |
Deprecated: use manyMonoidT with appropriate Monad like LazyIO and result Monoid like Endo instead
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.
:: (Monad m, Monoid a) | |
=> ExceptionalT e m a | atomic action to repeat |
-> ExceptionalT e m a |
We advise to use the Endo Monoid when you want to read a series of characters into a list. This means you use the difference lists technique in order to build the list, which is efficient.
import Data.Monoid (Endo, appEndo, ) import Control.Exception (try, ) import qualified Control.Monad.Exception.Synchronous as Sync
fmap (flip appEndo []) $ manyMonoidT (fromSynchronousMonoidT $ fmap (Endo . (:)) $ Sync.fromEitherT $ try getChar)
If you want Lazy IO you must additionally convert getChar
to LazyIO monad.
processToSynchronousT_ Source #
:: Monad m | |
=> (b -> Maybe (a, b)) | decons function |
-> (a -> ExceptionalT e m ()) | action that is run for each element fetched from |
-> Exceptional e b | value |
-> 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 actions 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 Data.List.HT.viewL
.
appendM :: (Monad m, Monoid a) => m (Exceptional e a) -> m (Exceptional e a) -> m (Exceptional e a) infixr 1 Source #
continueM :: (Monad m, Monoid a) => m (Maybe e) -> m (Exceptional e a) -> m (Exceptional e a) infixr 1 Source #