[Haskell-cafe] mtl: Why there is "Monoid w" constraint in the definition of class MonadWriter?

Petr P petr.mvd at gmail.com
Sun Dec 9 22:32:29 CET 2012


An additional thought: I'd say 'contained' is sort of inverse to 'writer':

   writer <=< contained   = id
   contained . writer     = return

Petr Pudlak


2012/12/9 Petr P <petr.mvd at gmail.com>

>   Hi all,
>
> I'd say that a type class declares functions and specifies laws (in the
> docs)
> what its implementations must adhere to. It's not the job of a type class
> to
> fulfill the laws, it's the job of its implementations. So the reason for
> 'Monoid w' in 'MonadWriter' cannot be that then 'MonadWriter' wouldn't be a
> monad. Such constraints should be required only by implementations.
>
> It is true that any Writer has an implicit underlying monoid, and we can
> even "extract" the operations from it as follows. The empty element can be
> extracted as
>
>      empty = liftM snd (listen (return ())) :: m w
>
> Having this 'empty', we can give 'const empty' to 'pass' to discard output
> of
> an action, so we can construct:
>
>     -- | @contained m@ executes the action @m@ in a contained environment
> and
>     -- returns its value and its output. The current output is not
> modified.
>     contained :: m a -> m (a, w)
>     contained k = do
>         -- we can retrieve mempty even if we don't have the monoid
> constraint:
>         ~(_, empty) <- listen (return ())
>         -- listen what @k@ does, get its result and ignore its output
> change:
>         pass (listen k >>= \x -> return (x, const empty))
>
> This generalizes 'listen' and 'pass' (both can be easily defined from it)
> and I find this function much easier to understand. In a way, it is also a
> generalization of WriterT's runWriterT, because for WriterT we have
> 'contained = lift . runWriterT'.
>
> [I implemented 'contained' in a fork of the mtl library, if anybody is
> interested: https://github.com/ppetr/mtl ]
>
> With that, we can do
>
>     -- Doesn't produce any output, only returns the combination
>     -- of the arguments.
>     append x y = liftM snd $ contained (tell x >> tell y) :: w -> w -> m w
>
> I didn't check the monoid laws, but it seems obvious that they follow from
> the
> monad laws and (a bit vague) specification of 'listen' and 'pass'.
>
> Personally, I'd find it better if `MonadWriter` would be split into two
> levels:
> One with just 'tell' and 'writer' and the next level extending it with
> 'listen'/'pass'/'contained'. The first level would allow things like
> logging to
> a file, without any monoidal structure. But this would break a lot of stuff
> (until we agree on and develop something like
> http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances).
>
>     Best regards,
>     Petr
>
>
>
> 2012/12/9 Roman Cheplyaka <roma at ro-che.info>
>
>> * Edward Z. Yang <ezyang at MIT.EDU> [2012-12-08 15:45:54-0800]
>> > > Second, even *if* the above holds (two tells are equivalent to one
>> > > tell), then there is *some* function f such that
>> > >
>> > >     tell w1 >> tell w2 == tell (f w1 w2)
>> > >
>> > > It isn't necessary that f coincides with mappend, or even that the
>> type
>> > > w is declared as a Monoid at all. The only thing we can tell from the
>> > > Monad laws is that that function f should be associative.
>> >
>> > Well, the function is associative: that's half of the way there to
>> > a monoid; all you need is the identity!  But we have those too:
>> > whatever the value of the execWriter (return ()) is...
>>
>> Let me repeat:
>>
>>   It isn't necessary that f coincides with mappend, or even that the
>>   type w is declared as a Monoid at all.
>>
>> Let me illustrate this with an example.
>>
>>   data MyWriter a = MyWriter Integer a
>>
>>   instance Monad MyWriter where
>>     return = MyWriter 0
>>     MyWriter n x >>= k =
>>       let MyWriter n' y = k x
>>       in MyWriter (n+n') y
>>
>>   instance MonadWriter Integer MyWriter where
>>     tell n = MyWriter n ()
>>     listen (MyWriter n x) = return (x,n)
>>     pass (MyWriter n (a,f)) = MyWriter (f n) a
>>
>> Yes, integers do form a monoid when equipped with 0 and (+). However, we
>> know well why they are not an instance of Monoid — namely, there's more
>> than one way they form a monoid.
>>
>> Even if something is in theory a monoid, there may be technical reasons
>> not to declare it a Monoid. Likewise, imposing a (technical) superclass
>> constraint on MonadWriter has nothing to do with whether the Monad will
>> be well-behaved.
>>
>> This is true in both directions: even if the type is an instance of
>> Monoid, nothing forces the Monad instance to use the Monoid instance.
>> I.e. I can declare a MonadWriter on the Sum newtype whose bind, instead
>> of adding, subtracts the numbers.
>>
>> Roman
>>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20121209/eb41549f/attachment.htm>


More information about the Haskell-Cafe mailing list