A question about mfix

What's wrong about giving mfix the following general definition?
mfix :: (a -> m a) -> m a mfix f = (mfix f) >>= f
I know it diverges if (>>=) is strict on the first argument. My question is, is this definition correct for all lazy monads? The documentation (http://haskell.org/ghc/docs/latest/html/libraries/base/ Control-Monad-Fix.html#v%3Amfix) says "mfix f executes the action f only once, with the eventual output fed back as the input.". So my definition looks like a valid one, doesn't it? I haven't fully wrapped my head around this monadic fixed-point thing yet. So, if you can give an example showing how my definition differs from a standard monad, that'll be great.

These aren't equivalent, at least with respect to sharing; consider the sharing behavior with respect to the Identity monad:
import Control.Monad.Fix import Control.Monad.Identity
mfixWei f = mfix f >>= f
v1, v2 :: [Int] v1 = runIdentity $ mfix $ \a -> return (0:a) v2 = runIdentity $ mfixWei $ \a -> return (0:a)
cons = (:)
While v1 and v2 are both infinite lists of zeros, v1 takes constant memory: v1 = cons 0 v1 but v2 takes memory linear in size to the last element evaluated: v2 = cons 0 t0 where t0 = cons 0 t1 t1 = cons 0 t2 t2 = cons 0 t3 t3 = ... This is where the specification about "executes the action f only once" comes from; your implementation expands to mfix f = mfix f >>= f = (mfix f >>= f) >>= f = ((mfix f >>= f) >>= f) >>= f = ... As you can see, f might get executed an arbitrary number of times depending on "how lazy" >>= is. Now, I don't know the answer if you "fix" (pardon the pun) your definition of mfix to
mfixLazy f = let x = x >>= f in x
which gives the correct sharing results in the "runIdentity" case.
-- ryan
On Tue, Jul 29, 2008 at 6:28 PM, Wei Hu
What's wrong about giving mfix the following general definition?
mfix :: (a -> m a) -> m a mfix f = (mfix f) >>= f
I know it diverges if (>>=) is strict on the first argument. My question is, is this definition correct for all lazy monads? The documentation (http://haskell.org/ghc/docs/latest/html/libraries/base/ Control-Monad-Fix.html#v%3Amfix) says "mfix f executes the action f only once, with the eventual output fed back as the input.". So my definition looks like a valid one, doesn't it?
I haven't fully wrapped my head around this monadic fixed-point thing yet. So, if you can give an example showing how my definition differs from a standard monad, that'll be great.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

So that's also why the fix function from Data.Function is defined as
fix f = let x = f x in x
instead of
fix f = f $ fix f
right? But, I think my mfix definition and your mfixLazy definition are still semantically equivalent because they expand to the same thing. See the following example:
import Control.Monad.Identity
-- Strict Identity monad data IdentityS a = IdentityS { runIdentityS :: a } deriving Show instance Monad IdentityS where return = IdentityS (IdentityS m) >>= k = k m
mfix' f = mfix' f >>= f mfixLazy f = let x = x >>= f in x
facFM f = return (\i -> if i == 0 then 1 else i * f (i - 1) )
-- correctly outputs 3! = 6 test = runIdentity (mfix facFM) 3
-- stack overflows test2 = runIdentityS (mfix' facFM) 3
-- hangs test3 = runIdentityS (mfixLazy facFM) 3
Thanks for pointing out the sharing part. My original question is still unanswered: for lazy monads, can we give such a general mfix definition?

On Wed, Jul 30, 2008 at 4:18 AM, Wei Hu
Thanks for pointing out the sharing part. My original question is still unanswered: for lazy monads, can we give such a general mfix definition?
I dunno. I played around with your definition and the mfix laws, and was unable to get anywhere. * mfix (return . h) = return (fix h) * mfix (\x -> a >>= \y -> f x y) = \y -> mfix (\x -> f x y) * if h is strict, mfix (liftM h . f) = liftM h (mfix (f . h)) * mfix (\x -> mfix (\y -> f x y)) = mfix (\x -> f x x) But I think this is the way to approach it. There are many kinds of "lazy monads", so presumably an exploration of this form will help characterize the kinds of monads for which this definition does work. Luke

Wei Hu wrote:
Thanks for pointing out the sharing part. My original question is still unanswered: for lazy monads, can we give such a general mfix definition?
I think Section 4.1 of http://doi.acm.org/10.1145/351240.351257 has the answer to that. The problem with the proposed general definition is that it computes the fixpoint not only for the values that are manipulated, but also for the involved effects. This doesn't show up for the Identity monad, since there are no effects then, but for more interesting monads the difference should become visible, not only with respect to sharing, but really with respect to the expected outcome of the computation. (Constructing an explicit counterexample is left as an exercise ;-) Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de

Janis Voigtlaender wrote:
Wei Hu wrote:
Thanks for pointing out the sharing part. My original question is still unanswered: for lazy monads, can we give such a general mfix definition?
... (Constructing an explicit counterexample is left as an exercise ;-)
Oh, I couldn't resist to do my own exercise ...
import Control.Monad.Fix import Control.Monad.State.Lazy
data Nat = S Nat | Z deriving Show
tick :: State Nat () tick = get >>= put . S
test1 = runState (mfix (const tick)) Z
test2 = runState (mfix (const tick)) Z where mfix f = (mfix f) >>= f
Now: *Main> test1 ((),S Z) *Main> test2 ((),S (S (S (S (S (S (S (S (S (S (S (S (S (S (S (S (S (S ........ I think that proves the point. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de
participants (4)
-
Janis Voigtlaender
-
Luke Palmer
-
Ryan Ingram
-
Wei Hu