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)

Hi Facundo,
The program below when loaded in ghci prints always False, and when compiled with ghc it prints True
From above, I guess the code is not compiled in ghci, which means byte-code is used insted of object-code.
If what matter here is "to get same result in ghci and compiled code",
invoking ghci with object code compilation option[1] may help. E.g.
start ghci with:
$ ghci -fobject-code
Below is a sample session with your code. I saved it as "UCSN.hs".
$ ls
UCSN.hs
$ ghc-7.4.1 --interactive UCSN.hs
GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling UCSN ( UCSN.hs, interpreted )
Ok, modules loaded: UCSN.
ghci> :main
type enter
False
ghci> :q
Leaving GHCi.
Invoking again, with "-fobject-code". Note the absense of "interpreted" message:
$ ghc-7.4.1 --interactive -fobject-code UCSN.hs
GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling UCSN ( UCSN.hs, UCSN.o )
Ok, modules loaded: UCSN.
ghci> :main
type enter
True
ghci> :q
Leaving GHCi.
Now we have "UCSN.hi" and "UCSN.o".
$ ls
UCSN.hi UCSN.hs UCSN.o
Invoking ghci again, without "-fobject-code".
No "interpreted" message. Showing 'True' with main.
$ ghc-7.4.1 --interactive UCSN.hs
GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Ok, modules loaded: UCSN.
ghci> :main
type enter
True
ghci> :q
Leaving GHCi.
Hope these help.
[1]: http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.html#...
Regards,
--
Atsuro
On Thu, Jun 28, 2012 at 6:41 AM, Facundo Domínguez
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@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Facundo Domínguez | Sent: 27 June 2012 22:41 | To: glasgow-haskell-users@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@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

I'm using StableNames to recover sharing in abstract syntax trees of
an embedded DSL, and I'm kind of following the approach of accelerate
[1]. I was expecting the stable name comparison to be slightly more
reliable. I'm pondering the alternatives.
Many thanks for the replies.
Facundo
[1] http://hackage.haskell.org/package/accelerate
On Thu, Jun 28, 2012 at 7:00 AM,
Send Glasgow-haskell-users mailing list submissions to glasgow-haskell-users@haskell.org
To subscribe or unsubscribe via the World Wide Web, visit http://www.haskell.org/mailman/listinfo/glasgow-haskell-users or, via email, send a message with subject or body 'help' to glasgow-haskell-users-request@haskell.org
You can reach the person managing the list at glasgow-haskell-users-owner@haskell.org
When replying, please edit your Subject line so it is more specific than "Re: Contents of Glasgow-haskell-users digest..."
Today's Topics:
1. Re: Fwd: ghc-7.6 branch (Gershom Bazerman) 2. Re: Strange behavior when using stable names inside ghci? (Atsuro Hoshino) 3. RE: API function to check whether one type fits "in" another (Simon Peyton-Jones) 4. RE: Strange behavior when using stable names inside ghci? (Simon Peyton-Jones)
----------------------------------------------------------------------
Message: 1 Date: Wed, 27 Jun 2012 19:22:55 -0400 From: Gershom Bazerman
Subject: Re: Fwd: ghc-7.6 branch To: glasgow-haskell-users@haskell.org Message-ID: <4FEB95CF.9090604@gmail.com> Content-Type: text/plain; charset=ISO-8859-1; format=flowed On 6/27/12 6:06 PM, Johan Tibell wrote:
This is not a theoretical issue. We have had all of the following problems happen in the past due to the current process:
* patches never making it upstream * releases of libraries without knowledge of the maintainer (who finds out by finding a new version of his/her package on Hackage.) * packages being released by GHC never ending up on Hackage, causing build breakages for people who use older GHCs and can't install the packages as they aren't available on Hackage.
At the almost certain risk of stepping into a discussion I don't fully understand, let me step into a discussion I almost certainly don't fully understand :-)
It seems to me that all these issues could be solved by having a member of the GHC team an assistant co-maintainer on packages that GHC depends on, and acting as such in a responsible manner, and in addition, having all packages bundled with GHC releases drawn from hackage releases. This is to say, that ghc-originated patches necessarily get committed to the upstream repo, because they must be there to be released on hackage, that ghc-originated patches necessarily get released to hackage because they must be there for GHC releases to draw on them, and maintainers necessarily know what gets released to hackage because they communicate well with co-maintainers.
This is different than community ownership -- packages are still owned and maintained by individuals. However, by having a ghc assistant co-maintainer, there's a specified conduit for collaboration. This is also different from the current situation, because a co-maintainer may only work on issues for GHC release compatibility, but they are acting as someone with direct responsibility for the package and as part of the team that "owns" the package.
Problems of collaboration aren't magiced away by this sort of change of titles, of course, but when there are problems of communication and collaboration, they can now be understood as and treated as problems between primary and secondary package maintainers.
I hope this makes some semblance of sense.
Cheers, Gershom
------------------------------
Message: 2 Date: Thu, 28 Jun 2012 15:49:27 +0900 From: Atsuro Hoshino
Subject: Re: Strange behavior when using stable names inside ghci? To: Facundo Dom?nguez Cc: glasgow-haskell-users@haskell.org Message-ID: Content-Type: text/plain; charset=ISO-8859-1 Hi Facundo,
The program below when loaded in ghci prints always False, and when compiled with ghc it prints True
From above, I guess the code is not compiled in ghci, which means byte-code is used insted of object-code.
If what matter here is "to get same result in ghci and compiled code", invoking ghci with object code compilation option[1] may help. E.g. start ghci with:
$ ghci -fobject-code
Below is a sample session with your code. I saved it as "UCSN.hs".
$ ls UCSN.hs $ ghc-7.4.1 --interactive UCSN.hs GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling UCSN ( UCSN.hs, interpreted ) Ok, modules loaded: UCSN. ghci> :main type enter False ghci> :q Leaving GHCi.
Invoking again, with "-fobject-code". Note the absense of "interpreted" message:
$ ghc-7.4.1 --interactive -fobject-code UCSN.hs GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling UCSN ( UCSN.hs, UCSN.o ) Ok, modules loaded: UCSN. ghci> :main type enter True ghci> :q Leaving GHCi.
Now we have "UCSN.hi" and "UCSN.o".
$ ls UCSN.hi UCSN.hs UCSN.o
Invoking ghci again, without "-fobject-code". No "interpreted" message. Showing 'True' with main.
$ ghc-7.4.1 --interactive UCSN.hs GHCi, version 7.4.1: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Ok, modules loaded: UCSN. ghci> :main type enter True ghci> :q Leaving GHCi.
Hope these help.
[1]: http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.html#...
Regards, -- Atsuro
On Thu, Jun 28, 2012 at 6:41 AM, 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)
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
------------------------------
Message: 3 Date: Thu, 28 Jun 2012 07:07:01 +0000 From: Simon Peyton-Jones
Subject: RE: API function to check whether one type fits "in" another To: "Philip K. F. H?lzenspies" Cc: "glasgow-haskell-users@haskell.org" Message-ID: <59543203684B2244980D7E4057D5FBC137907AC9@DB3EX14MBXC306.europe.corp.microsoft.com> Content-Type: text/plain; charset="iso-8859-1"
Philip
| What I'm looking for is a function | | fitsInto :: TermType -> HoleType -> Maybe [(TyVar,Type)]
Happily there is such a function, but you will need to become quite familiar with GHC's type inference engine.
We need to tighten up the specification first. I believe that you have function and argument, whose *most general types* are fun :: forall a b c. fun_ty arg :: forall p q. arg_ty You want to ask whether 'arg' could possibly be 'fun's second (say) argument.
To answer this you must first instantiate 'fun' correctly. For example, suppose fun :: forall a. [a] -> Int arg :: [Bool] Then we can indeed pass 'arg' to 'fun' but only if we instantiate 'fun' at Bool, thus: fun Bool :: [Bool] -> Int Now indeed the first argument of (fun Bool) has precisely type [Bool] and we are done.
This business of instantiating a polymorphic function with a type, using a type application (f Bool) is a fundamental part of how GHC works (and indeed type inference in general). If you aren't familiar with it, maybe try reading a couple of papers about GHC's intermediate language, System F or FC.
To play this game we have to correctly "guess" the type at which to instantiate 'fun'. This is what type inference does: we instantiate 'fun' with a unification variable 'alpha' meaning "I'm not sure" and then accumulate equality constraints that tell us what type 'alpha' stands for.
The other complication is that 'arg' might also need instantiation to fit, but I'll ignore that for now. It'll only show up in more complicated programs.
So you want a function something like this:
fits :: Type -- The type of the function -> Int -- Which argument position we are testing -> Type -- The argument -> TcM Bool -- Whether it fits
fits fun_ty arg_no arg_ty = do { inst_fun_ty <- deeplyInstantiate fun_ty ; llet (fun_arg_tys, fun_res_ty) = splitFunTys inst_fun_ty the_arg_ty = fun_arg_tys !! arg_no ; unifyType the_arg_ty arg_ty }
The first step instantiates the function type (deeplyInstantiate is in Inst.lhs) with fresh unification variables. The second extracts the appropriate argument. Then we unify the argument type the function expects with that of the supplied argument.
Even then you aren't done. Unification collects constraints, and we need to check they are solutle. So we'll really need something like
do { constraints <- captureConstriaints (fits fun_ty arg_no arg_ty) ; tcSimplifyTop constraints }
And the final thing you need to do is intiate the type checker monad with initTc, and check whether any errors occurred.
It occurs to me that a simpler way to do this might be to piggy back on the work of Thijs Alkemade [thijsalkemade@gmail.com] at Chalmers on "holes". He's going to make it possible to make an expression
fun _ arg
where the underscore means "hole". Then you can give this entire expression to the type checker and have it figure out whether it is typeable, and if so what the type the "_" is. This would mean you didn't need to do any of the above stuff (and I have simplified considerably in writing the above). Maybe look at the ticket http://hackage.haskell.org/trac/ghc/ticket/5910 and wiki page http://hackage.haskell.org/trac/ghc/wiki/Holes
Simon
------------------------------
Message: 4 Date: Thu, 28 Jun 2012 07:42:19 +0000 From: Simon Peyton-Jones
Subject: RE: Strange behavior when using stable names inside ghci? To: Facundo Dom?nguez , "glasgow-haskell-users@haskell.org" Message-ID: <59543203684B2244980D7E4057D5FBC137907E02@DB3EX14MBXC306.europe.corp.microsoft.com> Content-Type: text/plain; charset="iso-8859-1"
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@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Facundo Dom?nguez | Sent: 27 June 2012 22:41 | To: glasgow-haskell-users@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@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
------------------------------
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
End of Glasgow-haskell-users Digest, Vol 106, Issue 26 ******************************************************

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
participants (4)
-
Atsuro Hoshino
-
Facundo Domínguez
-
Simon Marlow
-
Simon Peyton-Jones