On 27/06/12 22:41, Facundo Domínguez wrote:
Hi,
The program below when loaded in ghci prints always False, and when
compiled with ghc it prints True. I'm using ghc-7.4.1 and I cannot
quite explain such behavior. Any hints?
Thanks in advance,
Facundo
{-# LANGUAGE GADTs #-}
import System.Mem.StableName
import Unsafe.Coerce
import GHC.Conc
data D where
D :: a -> b -> D
main = do
putStr "type enter"
s<- getLine
let i = fromEnum$ head$ s++"0"
d = D i i
case d of
D a b -> do
let a' = a
sn0<- pseq a'$ makeStableName a'
sn1<- pseq b$ makeStableName b
print (sn0==unsafeCoerce sn1)
GHCi adds some extra annotations around certain subexpressions to
support the debugger. This will make some things that would have equal
StableNames when compiled have unequal StableNames in GHCi. You would
see the same problem if you compile with -fhpc, which adds annotations
around every subexpression.
For your intended use of StableNames I imagine you can probably just
live with this limitation - others are doing the same (e.g. Accelerate
and Kansas Lava).
Cheers,
Simon
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users