
Nickolay Kudasov wrote:
Well, that they are heavily used in practice does not mean that they are actually useful in practice. The thing is that as soon as your functor is a monad, I don't think you really need the Free type anymore -- your instruction type is already a monad.
I don'tββ use that myself, so I leave this for others to answer. But you should note that `Free m` is not the same as `m`: e.g. if `m` is a probability monad `newtype P a = P [(Double, a)]`, then `Free P` gives you much more: the whole tree of probabilities (not only probs of final results), so one could traverse that tree. So I believe `Free m` is rather useful (as is deriving instances for `Free m` the way it is).
Yes, but in this case, Free P is useful *regardless* of P being a monad. If you didn't declare a monad instance for the P type, then you would still get the tree of probabilities. It bugs me that the functor is expected to already be a monad. The instance MonadState s m => MonadState s (Free m) is a fancy way of saying that if the instruction type m has two instructions get and put , then the free monad will have them as well. This is fine from the perspective of variant types, but we don't need to know that m is a monad for that. Furthermore, the MonadState class suggests that the usual laws for the state monad hold -- which they do not! Here a counterexample: {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-} import Control.Monad.State data Free f a = Return a | Free (f (Free f a)) instance Functor f => Monad (Free f) where return = Return (Free f) >>= k = Free $ fmap (>>= k) f instance MonadState s (Free (State s)) where state f = Free . state $ \s -> let (a,s') = f s in (Return a, s') interpret :: Free (State s) a -> (s -> s) interpret (Return a) s0 = s0 interpret (Free f ) s0 = snd (runState f s0) -- apply only the first instruction, skip the rest example1 = interpret (put 'a' >> get >> put 'b' >> get) undefined example2 = interpret (put 'b' >> get) undefined If we expect the usual laws for the state monad, then both example1 and example2 should be the same value. However, this is not the case: example1 = 'a' while example2 = 'b' . Just because you have two operations put and get doesn't mean that they can't have additional effects. And apparently, the MonadState condition is not strong enough to guarantee all the put/get laws.
(But I think it will be impossible for MonadCont).
It is. See https://github.com/ekmett/free/pull/33 for FreeT. FT has the instance in HEAD already.
That's surprising, I will have to check that. It appears to me that the MonadReader instance is only correct because the control operation is a morphism: local f (m >>= k) = local f m >>= local f . k Otherwise, I don't see how a general control operation can be lifted.
Almost, but not quite. The key qualification is "while still allowing pattern matching".
You'reββ right. But I think it is unnecessary for a library user to pattern match on F's structure. It is pattern matching on supplied functor that matters. And that ability is not lost.
A pattern match view :: F f a -> Either a (f (F f a)) that runs in O(1) time is very useful for implementing interpreters. For an example, see [1]. In particular, we can use the remainder to create new monadic actions with (>>=). The distinction is similar between being able to pattern match on (:) and using only fold to operate on lists. The former is more flexible. [1]: https://github.com/HeinrichApfelmus/operational/blob/master/doc/examples/Bre...
To summarize, I currently don't see what 'free' offers that the
'operational' package can't do equally well with only 11 exported symbols..
As far as I can tell, while with operational you can certainly do more things, free provides more things for free (these "baked algebraic laws"). free also provides some other interesting things, like iterative (co)monad trasformers, cofree comonads and free applicatives/alternatives (which are out of operational/free common area).
That all said, I don't feel myself concerned/experienced enough to state that one package should be preferred to another.
As mentioned, I'm not a fan of the "baked in algrebraic laws" because this excludes an optimization and many laws have to be written in the interpreter anyway. But you're saying that 'free' provides other free structures besides monads. That's a good point. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com