Copyright | (c) Gregory Crosswhite 2010 |
---|---|
License | BSD3 |
Maintainer | gcross@phys.washington.edu |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
This module provides a monad and a monad transformer that allow the user to abort a monadic computation and immediately return a result.
Synopsis
- type Abort r = AbortT r Identity
- runAbort :: Abort r r -> r
- newtype AbortT r m a = AbortT {
- unwrapAbortT :: m (Either r a)
- runAbortT :: Monad m => AbortT r m r -> m r
- abort :: Monad m => r -> AbortT r m a
- liftCallCC :: (((Either r a -> m (Either r b)) -> m (Either r a)) -> m (Either r a)) -> ((a -> AbortT r m b) -> AbortT r m a) -> AbortT r m a
- liftCatch :: (m (Either r a) -> (e -> m (Either r a)) -> m (Either r a)) -> AbortT r m a -> (e -> AbortT r m a) -> AbortT r m a
- liftListen :: Monad m => (m (Either r a) -> m (Either r a, w)) -> AbortT r m a -> AbortT r m (a, w)
- liftPass :: Monad m => (m (Either r a, w -> w) -> m (Either r a)) -> AbortT r m (a, w -> w) -> AbortT r m a
The Abort monad
type Abort r = AbortT r Identity Source #
An abort monad, parametrized by the type r
of the value to return.
:: Abort r r | the monadic computation to run |
-> r | the result of the computation |
Execute the abort monad computation and return the resulting value.
The AbortT monad transformer
An abort monad transformer parametrized by
r
- the value that will ultimately be returned; andm
- the inner monad.
The AbortT
type wraps a monadic value that is either
AbortT | |
|
Instances
MonadTrans (AbortT r) Source # | |
Defined in Control.Monad.Trans.Abort | |
Monad m => Monad (AbortT r m) Source # | |
Functor m => Functor (AbortT r m) Source # | |
Applicative m => Applicative (AbortT r m) Source # | |
Defined in Control.Monad.Trans.Abort | |
MonadIO m => MonadIO (AbortT r m) Source # | |
Defined in Control.Monad.Trans.Abort |
:: Monad m | |
=> AbortT r m r | the monadic computation to run |
-> m r | the (monadic) result of the computation |
Execute the abort monad computation and return the resulting (monadic) value.
Abort operations
:: Monad m | |
=> r | the result to return |
-> AbortT r m a | a monadic value that has the effect of terminating the computation and immediately returning a value; note that since all subsequent steps in the computation will be ignored, this monadic value can take an arbitrary type since its value will never be accessed |
Abort the computation and immediately return a result; all steps in the computation after this monadic computation will be ignored.
Note that since no further computation is performed after this, there is no way for subsequent computations to access the monadic value, and so it can be assigned an arbitrary type.
lifters
:: (((Either r a -> m (Either r b)) -> m (Either r a)) -> m (Either r a)) |
|
-> ((a -> AbortT r m b) -> AbortT r m a) |
|
-> AbortT r m a |
Lifts a callCC
operation to AbortT
.
:: (m (Either r a) -> (e -> m (Either r a)) -> m (Either r a)) |
|
-> AbortT r m a |
|
-> (e -> AbortT r m a) | Exception handler. |
-> AbortT r m a |
Lift a catchError
operation to AbortT
.