Copyright | (c) Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
- writer :: forall w m a. HasWriter w m => (a, w) -> m a
- tell :: HasWriter w m => w -> m ()
- type HasWriter w m = (Monoid w, SatisfyConstraint (IsWriter w) m)
- listen :: forall w m a. CanListen w m a => m a -> m (a, w)
- type CanListen w m a = SatisfyConstraintF (IsWriter w) m a (ListenFn w)
- type ListenFn w = Func MonadicValue (MkVarFnFrom (MonadicTuple w))
- pass :: forall w m a. CanPass w m a => m (a, w -> w) -> m a
- type CanPass w m a = SatisfyConstraintF (IsWriter w) m a (PassFn w)
- type PassFn w = MkVarFn (MonadicTuple (Endo w))
- newtype WriterT w m a :: * -> (* -> *) -> * -> * = WriterT {
- runWriterT :: m (a, w)
- class (Monoid w, MonadTower m) => IsWriter w m
Documentation
type HasWriter w m = (Monoid w, SatisfyConstraint (IsWriter w) m) Source
listen :: forall w m a. CanListen w m a => m a -> m (a, w) Source
Execute the action m
and add its output to the value of the
computation.
type CanListen w m a = SatisfyConstraintF (IsWriter w) m a (ListenFn w) Source
type ListenFn w = Func MonadicValue (MkVarFnFrom (MonadicTuple w)) Source
pass :: forall w m a. CanPass w m a => m (a, w -> w) -> m a Source
Execute the action m
(which returns a value and a function) and
returns the value, applying the function to the output.
type CanPass w m a = SatisfyConstraintF (IsWriter w) m a (PassFn w) Source
type PassFn w = MkVarFn (MonadicTuple (Endo w)) Source
newtype WriterT w m a :: * -> (* -> *) -> * -> *
A writer monad parameterized by:
w
- the output to accumulate.m
- The inner monad.
The return
function produces the output mempty
, while >>=
combines the outputs of the subcomputations using mappend
.
WriterT | |
|
class (Monoid w, MonadTower m) => IsWriter w m Source
The minimal definition needed for a monad providing a writer environment.
(Monoid w, MonadTower m) => IsWriter w (WriterT w m) | |
(Monoid w, MonadTower m) => IsWriter w (WriterT w m) | |
(Monoid w, MonadTower m) => IsWriter w (RWST r w s m) | |
(Monoid w, MonadTower m) => IsWriter w (RWST r w s m) | |
Monoid w => ValidConstraint (IsWriter w) | |
type ConstraintSatisfied (IsWriter w) m |