Stability of Uniques

Hi all, Consider the very simple test module Test2 where f = True When walking the AST after renaming I see that f has unique 1912603236 and True has unique 905969694. However, when walking the typechecked AST f seems to have unique 1627390565 instead. Should I expect that the unique associated with identifiers changes between renaming and typechecking? Or is there something else that I'm missing? Thanks! Edsko

Yes, locally-bound uniques change all the time, to maintain scoping hygiene. But top-level things from other modules have uniques that do not change. simon From: ghc-devs-bounces@haskell.org [mailto:ghc-devs-bounces@haskell.org] On Behalf Of Edsko de Vries Sent: 26 March 2013 15:05 To: ghc-devs@haskell.org Subject: Stability of Uniques Hi all, Consider the very simple test module Test2 where f = True When walking the AST after renaming I see that f has unique 1912603236 and True has unique 905969694. However, when walking the typechecked AST f seems to have unique 1627390565 instead. Should I expect that the unique associated with identifiers changes between renaming and typechecking? Or is there something else that I'm missing? Thanks! Edsko

So is there any way that I can see that an identifier in the renamed AST is
really the same as an identifier in the typechecked AST?
On Wed, Mar 27, 2013 at 1:57 PM, Simon Peyton-Jones
Yes, locally-bound uniques change all the time, to maintain scoping hygiene. But top-level things from other modules have uniques that do not change.****
** **
simon****
** **
*From:* ghc-devs-bounces@haskell.org [mailto:ghc-devs-bounces@haskell.org] *On Behalf Of *Edsko de Vries *Sent:* 26 March 2013 15:05 *To:* ghc-devs@haskell.org *Subject:* Stability of Uniques****
** **
Hi all,****
** **
Consider the very simple test****
** **
module Test2 where****
f = True****
** **
When walking the AST after renaming I see that f has unique 1912603236 and True has unique 905969694. However, when walking the typechecked AST f seems to have unique 1627390565 instead. Should I expect that the unique associated with identifiers changes between renaming and typechecking? Or is there something else that I'm missing?
Thanks!
Edsko****

Indeed the type checker does not actually clone identifiers.
ghc -c -ddump-rn -ddump-tc -dppr-debug Foo.hs
==================== Renamer ====================
nonrec {Foo.hs:3:1-8}
main:Foo.f{v r0}
main:Foo.f{v r0}
= {Foo.hs:3:5-8}
ghc-prim:GHC.Types.True{(w) d 6u}
<>
TYPE SIGNATURES
( main:Foo.f{v r0} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} ) :: ghc-prim:GHC.Types.Bool{(w) tc 3c}
TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base, ghc-prim, integer-gmp]
==================== Typechecker ====================
{Foo.hs:3:1-8}
AbsBinds
[]
[]
[( main:Foo.f{v r0} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} ) <= ( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )
<>]
( main:Foo.f{v r0} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )
:: ghc-prim:GHC.Types.Bool{(w) tc 3c}
[LclId]
{Foo.hs:3:1-8}
( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )
:: ghc-prim:GHC.Types.Bool{(w) tc 3c}
[LclId]
( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )
= {Foo.hs:3:5-8}
ghc-prim:GHC.Types.True{(w) v 6v}
<>
EvBinds{}
From: Edsko de Vries [mailto:edskodevries@gmail.com]
Sent: 27 March 2013 14:04
To: Simon Peyton-Jones
Cc: ghc-devs@haskell.org
Subject: Re: Stability of Uniques
So is there any way that I can see that an identifier in the renamed AST is really the same as an identifier in the typechecked AST?
On Wed, Mar 27, 2013 at 1:57 PM, Simon Peyton-Jones

Hmm. Thank you for pointing this out, it made me realize things are more
subtle than I had thought. The uniques in the typechecked AST correspond to
the 'abe_mono' field of ABExport (the monomorphic bindings within a binding
group), while the uniques in the renamed AST correspond to the 'abe_poly'
fields instead (you can see this in your example too).
Edsko
PS. Reading that "understanding the True Meaning of [ABExport] could get me
a PhD" in the ghc comments was a little frightening :)
On Wed, Mar 27, 2013 at 2:37 PM, Simon Peyton-Jones
Indeed the type checker does not actually clone identifiers. ****
** **
ghc -c -ddump-rn -ddump-tc -dppr-debug Foo.hs****
** **
==================== Renamer ====================****
nonrec {Foo.hs:3:1-8}****
main:Foo.f{v r0}****
main:Foo.*f{v r0}*****
= {Foo.hs:3:5-8}****
ghc-prim:GHC.Types.True{(w) d 6u}****
<>****
** **
TYPE SIGNATURES****
( main:Foo.f{v r0} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} ) :: ghc-prim:GHC.Types.Bool{(w) tc 3c}****
TYPE CONSTRUCTORS****
COERCION AXIOMS****
Dependent modules: []****
Dependent packages: [base, ghc-prim, integer-gmp]****
** **
==================== Typechecker ====================****
{Foo.hs:3:1-8}****
AbsBinds****
[]****
[]****
[( main:Foo*.f{v r0}* [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} ) <= ( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )****
<>]****
( main:Foo.f{v r0} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )****
:: ghc-prim:GHC.Types.Bool{(w) tc 3c}****
[LclId]****
{Foo.hs:3:1-8}****
( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )****
:: ghc-prim:GHC.Types.Bool{(w) tc 3c}****
[LclId]****
( f{v a9H} [lid] :: ghc-prim:GHC.Types.Bool{(w) tc 3c} )****
= {Foo.hs:3:5-8}****
ghc-prim:GHC.Types.True{(w) v 6v}****
<>****
EvBinds{}****
** **
** **
** **
*From:* Edsko de Vries [mailto:edskodevries@gmail.com] *Sent:* 27 March 2013 14:04 *To:* Simon Peyton-Jones *Cc:* ghc-devs@haskell.org *Subject:* Re: Stability of Uniques****
** **
So is there any way that I can see that an identifier in the renamed AST is really the same as an identifier in the typechecked AST?****
** **
On Wed, Mar 27, 2013 at 1:57 PM, Simon Peyton-Jones
wrote:**** Yes, locally-bound uniques change all the time, to maintain scoping hygiene. But top-level things from other modules have uniques that do not change.****
****
simon****
****
*From:* ghc-devs-bounces@haskell.org [mailto:ghc-devs-bounces@haskell.org] *On Behalf Of *Edsko de Vries *Sent:* 26 March 2013 15:05 *To:* ghc-devs@haskell.org *Subject:* Stability of Uniques****
****
Hi all,****
****
Consider the very simple test****
****
module Test2 where****
f = True****
****
When walking the AST after renaming I see that f has unique 1912603236 and True has unique 905969694. However, when walking the typechecked AST f seems to have unique 1627390565 instead. Should I expect that the unique associated with identifiers changes between renaming and typechecking? Or is there something else that I'm missing?
Thanks!
Edsko****
** **
participants (2)
-
Edsko de Vries
-
Simon Peyton-Jones