transformers-0.5.6.2: Concrete functor and monad transformers

Copyright(c) Ross Paterson 2017
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Select

Contents

Description

Selection monad transformer, modelling search algorithms.

Synopsis

The Select monad

type Select r = SelectT r Identity Source #

Selection monad.

select :: ((a -> r) -> a) -> Select r a Source #

Constructor for computations in the selection monad.

runSelect :: Select r a -> (a -> r) -> a Source #

Runs a Select computation with a function for evaluating answers to select a particular answer. (The inverse of select.)

mapSelect :: (a -> a) -> Select r a -> Select r a Source #

Apply a function to transform the result of a selection computation.

The SelectT monad transformer

newtype SelectT r m a Source #

Selection monad transformer.

SelectT is not a functor on the category of monads, and many operations cannot be lifted through it.

Constructors

SelectT ((a -> m r) -> m a) 
Instances
MonadTrans (SelectT r) Source # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

lift :: Monad m => m a -> SelectT r m a Source #

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

Defined in Control.Monad.Trans.Select

Methods

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

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

return :: a -> SelectT r m a #

fail :: String -> SelectT r m a #

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

Defined in Control.Monad.Trans.Select

Methods

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

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

MonadFail m => MonadFail (SelectT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

fail :: String -> SelectT r m a #

(Functor m, Monad m) => Applicative (SelectT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

pure :: a -> SelectT r m a #

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

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

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

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

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

Defined in Control.Monad.Trans.Select

Methods

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

(Functor m, MonadPlus m) => Alternative (SelectT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

empty :: SelectT r m a #

(<|>) :: SelectT r m a -> SelectT r m a -> SelectT r m a #

some :: SelectT r m a -> SelectT r m [a] #

many :: SelectT r m a -> SelectT r m [a] #

MonadPlus m => MonadPlus (SelectT r m) Source # 
Instance details

Defined in Control.Monad.Trans.Select

Methods

mzero :: SelectT r m a #

mplus :: SelectT r m a -> SelectT r m a -> SelectT r m a #

runSelectT :: SelectT r m a -> (a -> m r) -> m a Source #

Runs a SelectT computation with a function for evaluating answers to select a particular answer. (The inverse of select.)

mapSelectT :: (m a -> m a) -> SelectT r m a -> SelectT r m a Source #

Apply a function to transform the result of a selection computation. This has a more restricted type than the map operations for other monad transformers, because SelectT does not define a functor in the category of monads.

Monad transformation

selectToContT :: Monad m => SelectT r m a -> ContT r m a Source #

Convert a selection computation to a continuation-passing computation.

selectToCont :: Monad m => SelectT r m a -> ContT r m a Source #

Deprecated: Use selectToContT instead

Deprecated name for selectToContT.