> My strange evaluation problems could be reduced to the following
> code snippet:
> 
> --------------------------------------------------------------
> import Addr
> 
> foreign import ccall "malloc" unsafe malloc :: Int  -> IO Addr
> foreign import ccall "free"   unsafe free   :: Addr -> IO ()
> 
> main :: IO ()
> main = do
>    buf <- malloc 1
>    writeCharOffAddr buf 0 'X'
>    c <- readCharOffAddr buf 0
>    putStrLn "free"
>    free buf
>    print c
> --------------------------------------------------------------

Strictly speaking, GHC isn't doing anything wrong here.   The problem is
that readCharOffAddr looks like an IO operation, but it really isn't.
readCharOffAddr is defined like this:

        readCharOffAddr a i = 
                case indexCharOffAddr a i of 
                        { C# o# -> return (C# o#) }
 
where 

        indexCharOffAddr :: Addr -> Int -> Char

Note that indexCharOffAddr isn't an IO operation, so it's free to float
around and isn't constrained by the ordering of any the IO operations around
it.  There's nothing to stop GHC floating it past a "free", for example, if
the result of the indexCharOffAddr isn't required until later.

One workaround is to seq the result of readCharOffAddr before doing the
free, as you mentioned.  GHC won't rearrange evaluation across a seq,
because that would defeat the purpose of seq.

Perhaps readCharOffAddr should be defined as

        readCharOffAddr a i = 
                let c = indexCharOffAddr a i 
                in  c `seq` return c

(that appears to be the intention of whoever wrote the original version, but
I guess GHC has become cleverer since then :-)

But this version still isn't right: if you wrote

        do
                writeCharOffAddr ptr i c1
                d1 <- readCharOffAddr  ptr i
                writeCharOffAddr ptr i c2
                d2 <- readCharOffAddr  ptr i

then GHC would be free to common up the two instances of (readCharOffAddr
ptr i), so they would both return the same answer.  And it probably would,
too.

Sigh.  I guess we need real IO versions of readStuffOffAddr.  That means
adding another 9 primops, taking the total to 260 :-(

Cheers,
        Simon

Reply via email to