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)
_______________________________________________
Glasgow-haskell-users mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users