An answer and a question to GHC implementors [was Re: How to make Claessen's Refs Ord-able?]

Mike Gunter m@ryangunter.com
07 Apr 2002 18:28:20 -0700


A while back I asked how to make the Ref's from Koen Clasessen's PhD
thesis Ord-able for the purpose of making them keys for efficient
finite maps.

Koen quickly responded with a clever implementation which attaches the
values to the keys.  While I don't rule out eventually making use of
it, this solution has the drawback of requiring lookups in the finite
map to be inside the ST or IO monad.

Josef Svenningsson asked if I had tried adding 
  {-# NOINLINE refWInt #-}
I had (quite hopefully.)  It doesn't work.  After fiddling a bit to
get a sense of what works and what doesn't, I tried:
  {-# INLINE refWInt #-}
.  This does the trick!  I've included the working code (which differs
from that of my original message only by the addition of the INLINE
directive) below.

My question to the GHC implementors is: what's going on here?  Can you
give us (at least Josef and I are confused) any help in predicting how
unsafePerformIO will behave?

        thanks to all,
        mike


> import IOExts     ( IORef, newIORef, readIORef, writeIORef, unsafePerformIO )

> type    UniqTy    = Integer
> newtype RefWInt a = RefWInt (UniqTy, a)   deriving (Show)
>
> curUniqInt    :: IORef UniqTy
> curUniqInt    = unsafePerformIO (newIORef 0)
> newRef a  = do
>   v <- readIORef curUniqInt
>   writeIORef curUniqInt (v + 1)
>   return (v, a)
> 
> {-# INLINE refWInt #-}
> refWInt x = RefWInt (unsafePerformIO (newRef x))

which works properly for this program alone:

> tri_1 = (a, b, b1)
>   where a  = refWInt "a"
>     	  b  = refWInt "b"
>	  b1 = refWInt "b"

yielding (RefWInt (0,"a"),RefWInt (1,"b"),RefWInt (2,"b")).  

But if I add another copy of the same definition:

> tri_2 = (a, b, b1)
>   where a  = refWInt "a"
>	  b  = refWInt "b"
>	  b1 = refWInt "b"

and use it by uncommenting the second line here:

> main =   print tri_1
>       >> print tri_2

things only work with the INLINE directive.  Without it, I get:

  (RefWInt (0,"a"),RefWInt (1,"b"),RefWInt (1,"b"))
  (RefWInt (0,"a"),RefWInt (1,"b"),RefWInt (1,"b"))