[Haskell-cafe] free vs. operational vs. free-operational

Nickolay Kudasov nickolay.kudasov at gmail.com
Sat Nov 30 12:18:04 UTC 2013


>
> ​In the 'free' approach, I find it unpleasant that some laws are
> automatic from the functor type, while others have to be ensured by the
> interpreter. That's why 'operational' offers only one way to implement
> monads: everything has to be done in the interpreter.

​
As far as I know these instances are heavily used in practice, though they
are inconvenient in a way. Perhaps they could be moved in a separate
module. On the other hand one could use `FreeT` which derives instances in
a different manner.


> If you look at the transformer version  Control.Monad.Trans.Free , you
> will see that there are no MonadState instances -- as expected, because you
> have to specify the interaction of effects.


Some instances​​ are present in HEAD [1], just not on hackage yet. Some
other instances (MonadCont [2], MonadWriter [3]) are waiting for Edward
Kmett's approval.

Note that `Free` does not have "the true" set of mtl instances. While these
instances (derived from underlying functor) are heavily used in practice
for `Free`, `FreeT` suggests deriving instances from the transformed monad
(not underlying functor). It turns out the latter can be done for the most
part of MonadX instances (MonadWriter instance is somewhat questionable).
See some comments in [4].

That said, as we saw, Free can give you some laws automatically. However,
> this also has a drawback: Program has an optimization that Free can never
> have. Namely, Program gives you a (>>=) that can be used in a
> left-associative way (Think (((x ++ y) ++ z) ++ w) ) while still allowing
> pattern matching.


As far as I can tell, this corresponds to church encoded versions of `Free`
and `FreeT`, namely `F` and `FT`​​.
This is possible due to the work "Asymptotic Improvement of Computations
over Free Monads" by Janis Voightländer [5] and based on Edward Kmett's "Free
Monads for Less" series of articles [6,7]. `F` is on hackage already and
`FT` is in HEAD.

Best,
Nick

[1] https://github.com/ekmett/free
[2] https://github.com/ekmett/free/pull/33
[3] https://github.com/ekmett/free/issues/25
[4] https://github.com/ekmett/free/issues/31#issuecomment-28481426
[5] http://www.iai.uni-bonn.de/~jv/mpc08.pdf
[6] http://comonad.com/reader/2011/free-monads-for-less/
[7] http://comonad.com/reader/2011/free-monads-for-less-2/


2013/11/30 Heinrich Apfelmus <apfelmus at quantentunnel.de>

> Alejandro Serrano Mena wrote:
>
>> Dear Café,
>> I've been reading lately about the relation between the 'free' package and
>> the 'operational' package for rolling your own monads [1] [2].
>> Furthermore,
>> I've discovered that the 'free-operational' package, which is some sort of
>> bridge between the two worlds, and provides not only Monad but also
>> Applicative and Alternative instances for ProgramT.
>> The problem is that right now everything is a little confused in my head.
>> In particular, I have the following questions:
>>
>
> (Author of 'operational' here.)
>
>
>  - I've read that free allows you to 'bake algebraic laws' in the resulting
>> monad. How does this work? Why doesn't operational offer that feature?
>>
>
> What I mean by 'baking in algebraic laws' is the following: Consider the
> free monad over the functor
>
>    data F a = MZero | MPlus a a
>
>    mzero :: Free F a
>    mzero = Free MZero
>
>    mplus :: Free F a -> Free F a -> Free F a
>    mplus x y = Free (MPlus x y)
>
> For convenience, let me reproduce the relevant definitions for the free
> monad here
>
>    data Free f a = Return a | Free (f (Free f a))
>
>    (>>=) :: Functor f => Free f a -> (a -> Free f b) -> Free f b
>    (>>=) (Return a) k = k a
>    (>>=) (Free   x) k = Free (fmap (>>= k) x)
>
> Now, if you think about the definition of bind for a moment, you will see
> that it automatically guarantees a distributive law for  mplus :
>
>    mplus x y >>= k  =  mplus (x >>= k) (y >>= k)
>
> However, it turns out [1] that there is another law that you might want
>  mplus  to satisfy
>
>    mplus (return a) y = return a
>
> but which is incompatible with the distributive law. So, if you want to
> implement a monad where  mplus  should obey the latter law, you have to
> start with a different functor type F (which one?).
>
>
> In the 'free' approach, I find it unpleasant that some laws are automatic
> from the functor type, while others have to be ensured by the interpreter.
> That's why 'operational' offers only one way to implement monads:
> everything has to be done in the interpreter.
>
>   [1]: http://www.haskell.org/haskellwiki/MonadPlus
>
>
>
>  - One of the things I really like from the free package is that it
>> provides
>> support for many monad transformer stacks, whereas operational does not?
>> Is
>> there any special restriction why operational cannot do this? Would it be
>> possible to provide similar instances for free-operational?
>>
>
> There is a good reason why 'operational' cannot do this: in general, it is
> impossible to mix different effects in a general way. Why would
>
>    ProgramT SomeInstruction (State s)
>
> be a state monad as well even though  SomeInstruction  can introduce new
> effects?
>
> If you look at the monad transformer instances for  Free , like
> MonadState, you will notice that they require the functor to be that monad,
> i.e. they make use of the "baking in laws" effect. This is quite useless in
> practice, as writing a MonadState instance of the instruction type F is the
> same work as writing a MonadState instance for the  Free F  monad.
>
> If you look at the transformer version  Control.Monad.Trans.Free , you
> will see that there are no MonadState instances -- as expected, because you
> have to specify the interaction of effects.
>
>
>  - It seems that free gives more features (Alternative, Applicative) with
>> the same work. In which situations should I prefer operational to free? I
>> really like the separation between providing a data type and then a
>> interpretation that operational embodies...
>>
>
> Well, the features may look good on screen, but once you check the
> preconditions for the class instances, you will find that fulfilling them
> is as much work as writing the instance from scratch.
>
> The only two things that a free monad can give you is:
>
> * A  Monad  instance.
> * A way to pattern match on instructions and write an interpreter.
>
> This is what operational does. Everything else just shuffles work around,
> but doesn't alleviate it for you.
>
> That said, as we saw, Free can give you some laws automatically. However,
> this also has a drawback: Program has an optimization that Free can never
> have. Namely, Program gives you a (>>=) that can be used in a
> left-associative way (Think (((x ++ y) ++ z) ++ w) ) while still allowing
> pattern matching.
>
>
>  - Should I replace my usage of operational with free-operational
>> altogether?
>>
>
> I would say no, but then again, I'm the author of the 'operational'
> package. :)
>
>
> Best regards,
> Heinrich Apfelmus
>
> --
> http://apfelmus.nfshost.com
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131130/aa5ce2bd/attachment.html>


More information about the Haskell-Cafe mailing list