Improving containers library

Axel Simon Axel.Simon at in.tum.de
Sun Mar 7 10:19:10 EST 2010


On 06.03.2010, at 18:19, Bertram Felgenhauer wrote:

> Axel Simon wrote:
>>> Any easy way of comparing pointers? I mean, if I have something like
>>> Tree a = N | B (Tree a) a (Tree a)
>>> and have (l::Tree a) and (r::Tree a), can I ask about the "physical
>>> equality"?
>>
>> You can! Despite the names appearing in the following code, the
>> following is safe:
>>
>> -- | Equality on pointers.
>> ptrEqual :: a -> a -> Bool
>> ptrEqual x y = unsafePerformIO $ do
>>  nx <- makeStableName x
>>  ny <- makeStableName y
>>  return (nx==ny)
>
> {-# LANGUAGE MagicHash #-}
> import GHC.Exts
>
> ptrEqual' :: a -> a -> Bool
> ptrEqual' x y = case reallyUnsafePtrEquality# x y of
>    0# -> False
>    1# -> True
>
> This is actually a pointer comparison. I believe it can produce false
> negatives though, because indirections are not followed. If that's
> correct, a false negative may be turned into a positive by garbage
> collection. So use with care.

Interesting. But if reallyUnsafePtrEquality# is a primitive, it is  
evaluated either before or after GC, so it can't compare a pointer  
from one generation with the next.

Having ptrEqual return False if, in fact, the two values are identical  
is not a problem for the considered data structure. It merely implies  
that a structural comparison is performed which is slower.

Cheers,
Axel.

> regards,
>
> Bertram
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



More information about the Libraries mailing list