Portability | portable |
---|---|
Stability | experimental |
Maintainer | Merijn Verstraaten <merijn@inconsistent.nl> |
Safe Haskell | Safe-Inferred |
Control.Monad.Trans.Supply
Contents
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
,<|>
,mzero
andmplus
. - Example type:
-
orSupply
s aSupplyT
s f a - Difference from Control.Applicative.Supply:
- The
Applicative
instance ofSupplyT
defined in this module requires that the wrapped type is an instance ofMonad
. See the Applicative vs Monad section below for an in-depth explanation.
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.
- type Supply s a = SupplyT s Identity a
- data SupplyT s m a
- supply :: Monad m => (s -> m a) -> SupplyT s m a
- provide :: Monad m => (s -> a) -> SupplyT s m a
- demand :: Monad m => SupplyT s m s
- withSupply :: (s' -> s) -> Supply s a -> Supply s' a
- withSupplyT :: Functor f => (s' -> s) -> SupplyT s f a -> SupplyT s' f a
- runSupply :: Supply s a -> (s -> s) -> s -> a
- runSupplyT :: Monad m => SupplyT s m a -> (s -> s) -> s -> m a
- runListSupply :: Supply s a -> [s] -> Either (Supply s a) a
- runListSupplyT :: Monad m => SupplyT s m a -> [s] -> m (Either (SupplyT s m a) a)
- runMonadSupply :: Monad m => Supply s a -> m s -> m a
- runMonadSupplyT :: Monad m => SupplyT s m a -> m s -> m a
Applicative vs Monad SupplyT
𝐓𝐋;𝐃𝐑: Ignore Control.Applicative.Supply if you're wrapping a Monad
.
A Monad
instance of Supply
results in Supply
actions that can be
executed conditionally (after all, that's what Monad
s are for!),
implementing the SupplyT
in a way that allows this results in an important
restriction, it is impossible to define an Applicative
instance for
without a SupplyT
s m aMonad
instance for m
! As a result, it is not
possible to use this transformer to wrap something that is only
Applicative
and not Monad
and still get an Applicative
instance back.
To solve this issue, a slightly different transformer is implemented in
Control.Applicative.Supply, which does allow this!
Since it cannot be made an instance of Monad
, the
SupplyT
transformer from
Control.Applicative.Supply is less powerful than the one defined here. If
you're wrapping a Monad
, use the transformer defined in this module,
instead of the one defined in Control.Applicative.Supply.
Supply and SupplyT Type
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) |
Supply Operations
supply :: Monad m => (s -> m a) -> SupplyT s m aSource
Supply a construction function with an s
value from the supply.
provide :: Monad m => (s -> a) -> SupplyT s m aSource
Supply a non-monadic construction function with an s
value from the
supply and automatically lift its result into the m
monad that SupplyT
wraps.
withSupply :: (s' -> s) -> Supply s a -> Supply s' aSource
Change the type of values consumed by a Supply
computation.
withSupplyT :: Functor f => (s' -> s) -> SupplyT s f a -> SupplyT s' f aSource
Change the type of values consumed by a SupplyT
computation.
Running Supply Computations
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.
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.
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.
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.
runMonadSupply :: Monad m => Supply s a -> m s -> m aSource
Feed a supply consuming computation from a monadic action until the computation finishes.
runMonadSupplyT :: Monad m => SupplyT s m a -> m s -> m aSource
Feed a supply consuming computation from a monadic action until the computation finishes.