Strange behavior when using stable names inside ghci?

Simon Peyton-Jones simonpj at microsoft.com
Thu Jun 28 09:42:19 CEST 2012


You are, in effect, doing pointer equality here, which is certain to be fragile, ESPECIALLY if you are not optimising the code (as is the case in GHCi).  I'd be inclined to seek a more robust way to solve whatever problem you started with

Simon

|  -----Original Message-----
|  From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-
|  bounces at haskell.org] On Behalf Of Facundo Domínguez
|  Sent: 27 June 2012 22:41
|  To: glasgow-haskell-users at haskell.org
|  Subject: Strange behavior when using stable names inside ghci?
|  
|  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
|  Glasgow-haskell-users at haskell.org
|  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users





More information about the Glasgow-haskell-users mailing list