monad-state-0.2.0.1: Utility library for monads, particularly those involving state

Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Abort

Contents

Synopsis

Monads that can immediately return a result

class Monad m => MonadAbort m where Source

Associated Types

type AbortResultType m Source

Methods

abort :: AbortResultType m -> m a Source

The Abort monad

type Abort r = AbortT r Identity

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

runAbort

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 :: * -> (* -> *) -> * -> *

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

unwrapAbortT :: m (Either r a)
 

Instances

MonadTrans (AbortT r) 
Monad m => Monad (AbortT r m) 
Functor m => Functor (AbortT r m) 
Applicative m => Applicative (AbortT r m) 
MonadIO m => MonadIO (AbortT r m) 
MonadRWS m => MonadRWS (AbortT r m) 
MonadWriter m => MonadWriter (AbortT r m) 
MonadState m => MonadState (AbortT r m) 
MonadReader m => MonadReader (AbortT r m) 
MonadError m => MonadError (AbortT r m) 
MonadCont m => MonadCont (AbortT r m) 
Monad m => MonadAbort (AbortT r m) 
type WriterType (AbortT r m) = WriterType m 
type StateType (AbortT r m) = StateType m 
type EnvType (AbortT r m) = EnvType m 
type ErrorType (AbortT r m) = ErrorType m 
type AbortResultType (AbortT r m) = r 

runAbortT

Arguments

:: forall (m :: * -> *). 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.

AbortT operations

mapAbortT :: (m (Either r a) -> n (Either r' b)) -> AbortT r m a -> AbortT r' n b Source