| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | Merijn Verstraaten <merijn@inconsistent.nl> |
| Safe Haskell | Safe-Inferred |
Control.Monad.Supply
Description
- Computation type:
- Computations that require a supply of values.
- Binding strategy:
- Applicative values are functions that consume an input from a supply to produce a value.
- Useful for:
- Providing a supply of unique names or other values to computations needing them.
- Zero and plus:
- Identical to the underlying implementations (if any) of
empty,<|>,mzeroandmplus.
The monad represents a computation that consumes a supply of
Supply s as's to produce a value of type a. One example use is to simplify
computations that require the generation of unique names. The Supply monad
can be used to provide a stream of unique names to such a computation.
- class Monad m => MonadSupply s f m | m -> s, m -> f where
- demand :: MonadSupply s f m => m s
- type Supply s a = SupplyT s Identity a
- withSupply :: (s' -> s) -> Supply s a -> Supply s' a
- runSupply :: Supply s a -> (s -> s) -> s -> a
- runListSupply :: Supply s a -> [s] -> Either (Supply s a) a
- runMonadSupply :: Monad m => Supply s a -> m s -> m a
- data SupplyT s m a
- withSupplyT :: Functor f => (s' -> s) -> SupplyT s f a -> SupplyT s' f a
- runSupplyT :: Monad m => SupplyT s m a -> (s -> s) -> s -> m a
- runListSupplyT :: Monad m => SupplyT s m a -> [s] -> m (Either (SupplyT s m a) a)
- runMonadSupplyT :: Monad m => SupplyT s m a -> m s -> m a
- module Control.Monad
- module Control.Monad.Trans
The MonadSupply Class
class Monad m => MonadSupply s f m | m -> s, m -> f whereSource
The MonadSupply class provides access to the functions needed to
construct supply-consuming computations in a monad transformer stack.
Methods
supply :: (s -> f a) -> m aSource
Supply a construction function with an s value from the supply,
the f in the function's type refers to the monad wrapped by SupplyT.
provide :: (s -> a) -> m aSource
Provide a non-monadic construction function with an s value from the
supply and automatically lift its result into the f monad that
SupplyT wraps.
Instances
| MonadSupply s f m => MonadSupply s f (MaybeT m) | |
| MonadSupply s f m => MonadSupply s f (ListT m) | |
| MonadSupply s f m => MonadSupply s f (IdentityT m) | |
| (Monoid w, MonadSupply s f m) => MonadSupply s f (WriterT w m) | |
| (Monoid w, MonadSupply s f m) => MonadSupply s f (WriterT w m) | |
| MonadSupply s f m => MonadSupply s f (StateT s m) | |
| MonadSupply s f m => MonadSupply s f (StateT s m) | |
| MonadSupply s f m => MonadSupply s f (ReaderT r m) | |
| (Error e, MonadSupply s f m) => MonadSupply s f (ErrorT e m) | |
| MonadSupply s f m => MonadSupply s f (ContT r m) | |
| (Functor m, Monad m) => MonadSupply s m (SupplyT s m) | |
| (Monoid w, MonadSupply s f m) => MonadSupply s f (RWST r w s m) | |
| (Monoid w, MonadSupply s f m) => MonadSupply s f (RWST r w s m) |
demand :: MonadSupply s f m => m sSource
Demand an s value from the supply.
The Supply Monad
withSupply :: (s' -> s) -> Supply s a -> Supply s' aSource
Change the type of values consumed by a Supply computation.
runSupply :: Supply s a -> (s -> s) -> s -> aSource
Run a supply consuming computation, using a generation function and
initial value to compute the values consumed by the Supply computation.
runListSupply :: Supply s a -> [s] -> Either (Supply s a) aSource
Feed a supply consuming computation from a list until the computation
finishes or the list runs out. If the list does not contain sufficient
elements, runListSupply returns uncompleted computation.
runMonadSupply :: Monad m => Supply s a -> m s -> m aSource
Feed a supply consuming computation from a monadic action until the computation finishes.
The Supply Monad Transformer
The Supply transformer.
Composes Supply with an underlying monad, allowing it to be used monad in transformer stacks.
The resulting SupplyT value has Alternative and MonadPlus instances if
the underlying monad has such these instances.
Instances
| (Functor m, Monad m) => MonadSupply s m (SupplyT s m) | |
| MonadTrans (SupplyT s) | |
| (Functor m, Monad m) => Monad (SupplyT s m) | |
| Functor f => Functor (SupplyT s f) | |
| (Functor m, MonadPlus m) => MonadPlus (SupplyT s m) | |
| (Functor m, Monad m) => Applicative (SupplyT s m) | |
| (Alternative m, Monad m) => Alternative (SupplyT s m) | |
| (Functor m, MonadIO m) => MonadIO (SupplyT s m) |
withSupplyT :: Functor f => (s' -> s) -> SupplyT s f a -> SupplyT s' f aSource
Change the type of values consumed by a SupplyT computation.
runSupplyT :: Monad m => SupplyT s m a -> (s -> s) -> s -> m aSource
Run a supply consuming computation, using a generation function and
initial value to compute the values consumed by the SupplyT computation.
runListSupplyT :: Monad m => SupplyT s m a -> [s] -> m (Either (SupplyT s m a) a)Source
Feed a supply consuming computation from a list until the computation
finishes or the list runs out. If the list does not contain sufficient
elements, runListSupplyT returns uncompleted computation.
runMonadSupplyT :: Monad m => SupplyT s m a -> m s -> m aSource
Feed a supply consuming computation from a monadic action until the computation finishes.
module Control.Monad
module Control.Monad.Trans