| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Weighted
Contents
Description
This module provides monad transformer similar to
WriterT, implemented using StateT, making it
tail recursive. (The traditional writer always leaks space: see
here
for more information).
Pattern Synonyms
are used to provide the same interface as
WriterT. Unfortunately, current GHC warns
whenever these patterns are used that there are unmatched patterns: the
COMPLETE pragma should solve
this problem in future version of GHC.
A pattern synonym is also provided for a non-transformer version of writer.
Again, this is just StateT underneath, but its interface looks as if it was
defined like so:
newtype Writer w a = Writer { runWriter :: (a, w) }The other difference between this monad and
WriterT is that it relies on <.> from
Semiring, rather than mappend from Monoid.
- data WeightedT s m a
- runWeightedT :: Semiring s => WeightedT s m a -> m (a, s)
- pattern WeightedT :: forall m s a. (Functor m, Semiring s) => m (a, s) -> WeightedT s m a
- execWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m s
- evalWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m a
- type Weighted s = WeightedT s Identity
- runWeighted :: Semiring s => Weighted s a -> (a, s)
- pattern Weighted :: forall s a. Semiring s => (a, s) -> Weighted s a
- execWeighted :: Semiring s => Weighted s a -> s
- evalWeighted :: Semiring s => Weighted s a -> a
Transformer
A monad transformer similar to WriterT, except
that it does not leak space. It is implemented using a state monad, so that
mappend is tail recursive. See
this
email to the Haskell libraries committee for more information.
It also uses <.> from Semiring, rather than mappend from Monoid when
combining computations.
Wherever possible, coercions are used to eliminate any overhead from the newtype wrapper.
Instances
runWeightedT :: Semiring s => WeightedT s m a -> m (a, s) Source #
Run a weighted computation in the underlying monad.
execWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m s Source #
Run a weighted computation in the underlying monad, and collect its weight.
evalWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m a Source #
Run a weighted computation in the underlying monad, and return its result.
Plain
type Weighted s = WeightedT s Identity Source #
A type synonym for the plain (non-transformer) version of Weighted. This
can be used as if it were defined as:
newtype Weighted w a = Weighted { runWeighted :: (a, w) }runWeighted :: Semiring s => Weighted s a -> (a, s) Source #
Run a weighted computation.
>>>runWeighted $ traverse (\x -> Weighted (show x, x)) [1..5](["1","2","3","4","5"],120)
pattern Weighted :: forall s a. Semiring s => (a, s) -> Weighted s a Source #
This pattern gives the newtype wrapper around StateT the same interface
as as if it was defined like so:
newtype Weighted w a = Weighted { runWeighted :: (a, w) }Unfortunately GHC warns that a function is incomplete wherever this pattern is used. This issue should be solved in a future version of GHC, when the COMPLETE pragma is implemented.
>>>execWeighted $ traverse (\x -> Weighted ((), x)) [1..5]120
execWeighted :: Semiring s => Weighted s a -> s Source #
Run a weighted computation, and collect its weight.
evalWeighted :: Semiring s => Weighted s a -> a Source #
Run a weighted computation, and return its result.