AbortT-transformers-1.0.1.3: A monad and monadic transformer providing "abort" functionality

Copyright(c) Gregory Crosswhite 2010
LicenseBSD3
Maintainergcross@phys.washington.edu
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Abort

Contents

Description

This module provides a monad and a monad transformer that allow the user to abort a monadic computation and immediately return a result.

Synopsis

The Abort monad

type Abort r = AbortT r Identity Source #

An abort monad, parametrized by the type r of the value to return.

runAbort Source #

Arguments

:: 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

newtype AbortT r m a Source #

An abort monad transformer parametrized by

  • r - the value that will ultimately be returned; and
  • m - the inner monad.

The AbortT type wraps a monadic value that is either

  • Left r, which indicates that the monadic computation has terminated with result r and so all further steps in the computation should be ignored; or
  • Right a, which indicates that the computation is proceding normally and that its current value is a.

Constructors

AbortT 

Fields

Instances
MonadTrans (AbortT r) Source # 
Instance details

Defined in Control.Monad.Trans.Abort

Methods

lift :: Monad m => m a -> AbortT r m a #

Monad m => Monad (AbortT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Abort

Methods

(>>=) :: AbortT r m a -> (a -> AbortT r m b) -> AbortT r m b #

(>>) :: AbortT r m a -> AbortT r m b -> AbortT r m b #

return :: a -> AbortT r m a #

fail :: String -> AbortT r m a #

Functor m => Functor (AbortT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Abort

Methods

fmap :: (a -> b) -> AbortT r m a -> AbortT r m b #

(<$) :: a -> AbortT r m b -> AbortT r m a #

Applicative m => Applicative (AbortT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Abort

Methods

pure :: a -> AbortT r m a #

(<*>) :: AbortT r m (a -> b) -> AbortT r m a -> AbortT r m b #

liftA2 :: (a -> b -> c) -> AbortT r m a -> AbortT r m b -> AbortT r m c #

(*>) :: AbortT r m a -> AbortT r m b -> AbortT r m b #

(<*) :: AbortT r m a -> AbortT r m b -> AbortT r m a #

MonadIO m => MonadIO (AbortT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Abort

Methods

liftIO :: IO a -> AbortT r m a #

runAbortT Source #

Arguments

:: 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

abort Source #

Arguments

:: 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

liftCallCC Source #

Arguments

:: (((Either r a -> m (Either r b)) -> m (Either r a)) -> m (Either r a))

callCC on the argument monad.

-> ((a -> AbortT r m b) -> AbortT r m a)

AbortT action that receives the continuation

-> AbortT r m a 

Lifts a callCC operation to AbortT.

liftCatch Source #

Arguments

:: (m (Either r a) -> (e -> m (Either r a)) -> m (Either r a))

catch on the argument monad.

-> AbortT r m a

AbortT action to attempt.

-> (e -> AbortT r m a)

Exception handler.

-> AbortT r m a 

Lift a catchError operation to AbortT.

liftListen Source #

Arguments

:: Monad m 
=> (m (Either r a) -> m (Either r a, w))

listen on the argument monad.

-> AbortT r m a

AbortT action to run.

-> AbortT r m (a, w) 

Lift a listen operation to the new monad.

liftPass Source #

Arguments

:: Monad m 
=> (m (Either r a, w -> w) -> m (Either r a))

pass on the argument monad.

-> AbortT r m (a, w -> w)

AbortT action to run.

-> AbortT r m a 

Lift a pass operation to the new monad.