Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines a capability type class for writer effects. A writer program can
output values with tell
. The values output by two consecutive
sub-computation are combined using a monoid's mappend
.
The interface of HasWriter
follows that of
MonadWriter
. However, this module does not
include a strategy to provide a HasWriter
capability from a MonadWriter
instance. It is generally a bad idea to use monads such as
WriterT
, as they tend to leak space, as
described in this
<https://blog.infinitenegativeutility.com/2016/7/writer-monads-and-space-leaks
blog post> by Getty Ritter.
Instead, you should use the WriterLog
strategy that implements the writer
monad on a state monad. There is no downside, as using HasWriter
instead of
HasState
directly ensures your code adheres to the writer monad interface
and does not misuse the underlying state monad.
Synopsis
- class (Monoid w, Monad m, HasSink tag w m) => HasWriter (tag :: k) (w :: *) (m :: * -> *) | tag m -> w where
- writer :: forall tag w m a. HasWriter tag w m => (a, w) -> m a
- tell :: forall tag w m. HasWriter tag w m => w -> m ()
- listen :: forall tag w m a. HasWriter tag w m => m a -> m (a, w)
- pass :: forall tag w m a. HasWriter tag w m => m (a, w -> w) -> m a
- type HasWriter' (tag :: k) = HasWriter tag (TypeOf k tag)
- type family TypeOf k (s :: k) :: *
- type WriterLog = SinkLog
- type StreamLog = SinkLog
- newtype SinkLog m (a :: *) = SinkLog (m a)
- module Capability.Accessors
Relational capability
class (Monoid w, Monad m, HasSink tag w m) => HasWriter (tag :: k) (w :: *) (m :: * -> *) | tag m -> w where Source #
Writer capability
An instance should fulfill the following laws. At this point these laws are not definitive, see https://github.com/haskell/mtl/issues/5.
listen @t (pure a) = pure (a, mempty)
listen @t (tell @t w) = tell @t w >> pure (w, w)
listen @t (m >>= k) = listen @t m >>= \(a, w1) -> listen @t (k a) >>= \(b, w2) -> pure (b, w1 `mappend` w2)
pass @t (tell @t w >> pure (a, f)) = tell @t (f w) >> pure a
writer @t (a, w) = tell @t w >> pure a
A note on the HasSink
super class.
HasSink
offers one yield
method with the same signature as tell
.
Many people's intuition, however, wouldn't connect the two: yield
ing
tosses the value down some black-box chute, while tell
ing grows and
accumulation via the monoid. The connection is since the chute
is opaque,
the tosser cannot rule out there being such an accumulation at the chutes
other end.
Formally, we reach the same conclusion. HasSink
has no laws,
indicating the user can make no assumptions beyond the signature of yield
.
HasWriter
, with tell
defined as yield
, is thus always compatable
regardless of whatever additional methods it provides and laws by which it
abides.
writer_ :: Proxy# tag -> (a, w) -> m a Source #
For technical reasons, this method needs an extra proxy argument.
You only need it if you are defining new instances of HasReader
.
Otherwise, you will want to use writer
.
See writer
for more documentation.
Instances
(Monoid w, HasState tag w m) => HasWriter (tag :: k) w (WriterLog m) Source # | |
(forall x. Coercible (m x) (t2 (t1 m) x), Monad m, HasWriter tag w (t2 (t1 m))) => HasWriter (tag :: k) w ((t2 :.: t1) m) Source # | Compose two accessors. |
(HasWriter tag w m, MonadTransUnlift t, Monad (t m)) => HasWriter (tag :: Type) w (Lift (t m)) Source # | Lift one layer in a monad transformer stack. Note, that if the deriving (HasWriter tag w) via WriterLog (Lift (SomeTrans (MonadState SomeStateMonad))) over deriving (HasWriter tag w) via Lift (SomeTrans (WriterLog (MonadState SomeStateMonad))) |
writer :: forall tag w m a. HasWriter tag w m => (a, w) -> m a Source #
writer @tag (a, w)
lifts a pure writer action (a, w)
to a monadic action in an arbitrary
monad m
with capability HasWriter
.
Appends w
to the output of the writer capability tag
and returns the value a
.
tell :: forall tag w m. HasWriter tag w m => w -> m () Source #
tell @tag w
appends w
to the output of the writer capability tag
.
listen :: forall tag w m a. HasWriter tag w m => m a -> m (a, w) Source #
listen @tag m
executes the action m
and returns the output of m
in the writer capability tag
along with result of m
.
Appends the output of m
to the output of the writer capability tag
.
pass :: forall tag w m a. HasWriter tag w m => m (a, w -> w) -> m a Source #
pass @tag m
executes the action m
. Assuming m
returns (a, f)
and appends
w
to the output of the writer capability tag
.
pass @tag m
instead appends w' = f w
to the output and returns a
.
Functional capability
type HasWriter' (tag :: k) = HasWriter tag (TypeOf k tag) Source #
type family TypeOf k (s :: k) :: * Source #
Type family associating a tag to the corresponding type. It is intended to simplify constraint declarations, by removing the need to redundantly specify the type associated to a tag.
It is poly-kinded, which allows users to define their own kind of tags.
Standard haskell types can also be used as tags by specifying the *
kind
when defining the type family instance.
Defining TypeOf
instances for Symbol
s (typelevel string
literals) is discouraged. Since symbols all belong to the same global
namespace, such instances could conflict with others defined in external
libraries. More generally, as for typeclasses, TypeOf
instances should
always be defined in the same module as the tag type to prevent issues due to
orphan instances.
Example:
import Capability.Reader data Foo data Bar type instance TypeOf * Foo = Int type instance TypeOf * Bar = String -- Same as: foo :: HasReader Foo Int M => … foo :: HasReader' Foo m => … foo = …
Strategies
newtype SinkLog m (a :: *) Source #
Accumulate sunk values with their own monoid.
SinkLog (m a) |
Instances
(Monoid w, HasState tag w m) => HasSink (tag :: k) w (SinkLog m) Source # | |
(Monoid w, HasState tag w m) => HasWriter (tag :: k) w (WriterLog m) Source # | |
Monad m => Monad (SinkLog m) Source # | |
Functor m => Functor (SinkLog m) Source # | |
Applicative m => Applicative (SinkLog m) Source # | |
Defined in Capability.Sink.Internal.Strategies | |
MonadIO m => MonadIO (SinkLog m) Source # | |
Defined in Capability.Sink.Internal.Strategies | |
PrimMonad m => PrimMonad (SinkLog m) Source # | |
type PrimState (SinkLog m) Source # | |
Defined in Capability.Sink.Internal.Strategies |
Modifiers
module Capability.Accessors