mfix as an effect

oleg at pobox.com oleg at pobox.com
Sun Jan 11 16:55:08 EST 2004


Can mfix be considered as "just a fix point combinator", without
any trace of effect?

The recent discussion about continuations and implementations of
Scheme in Haskell highlighted that question. The point of the
discussion is the difference between letrec implemented using the
fixpoint combinator, and a letrec implemented via an updateable cell
(as in Scheme, according to R5RS).

Ashley Yakeley wrote:

> > The difference between the Y and set! approaches to letrec *is*
> > observable.

> I don't believe you. My implementation uses Haskell's "mfix", which 
> looks like a Y to me. I certainly don't use anything like "set!".

That is, Ashley Yakeley claimed that his Haskell implementation of
Scheme implements letrec via Y -- and yet his implementation is
consistent with the R5RS semantics, which mandates the updateable-cell
letrec. Indeed, his implementation passes the tests designed to
discern the way letrec is implemented.

There seems to be a contradiction in the above statements. The
contradiction is resolved by noting that "mfix", although may look
like "Y", is fundamentally different. There is a latent "set!" in
mfix, which can be pried open with call/cc. There is an effect in
mfix. The following is a simple test that shows it.

Let us consider the following test (Scheme code first, Haskell code
follows).

(letrec
    ((fact
      (cons #f
            (lambda (n)
              (set-car! fact #t)
              (if (zero? n) 1
                  (* n ((cdr fact) (- n 1))))))))
  (let* ((before (car fact))
         (res ((cdr fact) 5)))
    (list before res (car fact))))

The test has been introduced and discussed in
http://google.com/groups?selm=200102240312.TAA11588%40adric.cs.nps.navy.mil


If letrec is implemented via updates, the test returns (#f 120 #t)
If letrec is implemented via Y, the test should return (#f 120
#f). It is easy to see that if we use Y defined by (Y f) = f (Y f),
the result indeed must be (#f 120 #f).

Now, let us implement letrec in Haskell via fix and mfix, and compare
the results. First, the implementation of the test via fix

> import Data.IORef
> import System.IO.Unsafe
> import Control.Monad.Fix (mfix)

> fix f = f g where g = f g
> g = \f -> newIORef
>           (False, \n -> do
> 	                    (flag,body) <- readIORef f
> 			    writeIORef f (True,body)
> 			    res <- if n ==0 then return 1 else
> 			           body (n-1) >>= return . (* n)
> 			    return res)
>
> g1 = \f -> unsafePerformIO (g f)
>
> test = let fact = fix g1 in do 
>                              (flag,body) <- readIORef fact
> 			       res <- (body 5)
> 			       (flag',_) <- readIORef fact
> 			       return (flag, res,flag')


The code matches the Scheme code in every detail. If we try

> *Main> test >>= putStrLn . show
> (False,120,False)

we obtain the expected result. Now, we bring in mfix:

> test2 = do 
>          fact <- mfix g
> 	   (flag,body) <- readIORef fact
> 	   res <- (body 5)
> 	   (flag',_) <- readIORef fact
> 	   return (flag, res,flag')

And, quite predictably,

> *Main> test2 >>= putStrLn . show
> (False,120,True)




More information about the Haskell mailing list