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.
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.
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.
Alejandro Serrano Mena wrote:(Author of 'operational' here.)
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:
What I mean by 'baking in algebraic laws' is the following: Consider the free monad over the functor
- 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?
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/MonadPlusThere is a good reason why 'operational' cannot do this: in general, it is impossible to mix different effects in a general way. Why would
- 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?
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.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.
- 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...
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.I would say no, but then again, I'm the author of the 'operational' package. :)
- Should I replace my usage of operational with free-operational altogether?
Best regards,
Heinrich Apfelmus
--
http://apfelmus.nfshost.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe