Why do Names defined in the current module lack a module name?
Simon Peyton-Jones
simonpj at microsoft.com
Wed Apr 3 14:14:52 CEST 2013
I've just been checking. The top level name *is* (and remains) an External Name. See below.
Don't be misled by the dump labelled "Typechecker" (-ddump-tc). It is carefully printing things as in error messages, with as little qualification as possible; since 'mysum' is in scope unqualified here, it's printed unqualified. But it's an External Name all right. Use -dppr-debug to see it in its full glory
Simon
==================== Renamer ====================
Foo.mysum :: [Int] -> Int
Foo.mysum xs = foldl' (+) 0 xs
TYPE SIGNATURES
mysum :: [Int] -> Int
TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base, ghc-prim, integer-gmp]
==================== Typechecker ====================
AbsBinds
[]
[]
[mysum <= mysum
<>]
mysum :: [Int] -> Int
[LclId]
mysum xs = foldl' ((+)) 0 xs
==================== Desugar (after optimization) ====================
Result size = 11
Foo.mysum :: [GHC.Types.Int] -> GHC.Types.Int
[LclIdX]
Foo.mysum =
\ (xs_abz :: [GHC.Types.Int]) ->
Data.List.foldl'
@ GHC.Types.Int
@ GHC.Types.Int
(GHC.Num.+ @ GHC.Types.Int GHC.Num.$fNumInt)
(GHC.Types.I# 0)
xs_abz
| -----Original Message-----
| From: Johan Tibell [mailto:johan.tibell at gmail.com]
| Sent: 02 April 2013 17:43
| To: Simon Peyton-Jones
| Cc: ghc-devs at haskell.org
| Subject: Re: Why do Names defined in the current module lack a module
| name?
|
| Hi Simon,
|
| On Tue, Apr 2, 2013 at 3:31 AM, Simon Peyton-Jones
| <simonpj at microsoft.com> wrote:
| >
| > Does this help
| >
| > http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/NameType
|
| A bit, but it's still not clear to me exactly when user defined exported
| entities will have full (i.e. including module) names.
|
| > Something that starts top-level may not finish up as top-level.
| Nested bindings are never qualified.
| >
| > After TidyPgm, externally-visible names (to the linker) are qualified,
| ones local to the .o file are not.
|
| Here's my example program:
|
| ```haskell
| module Test
| ( mysum
| ) where
|
| import Data.List (foldl')
|
| import Import (imported)
|
| mysum :: [Int] -> Int
| mysum xs = foldl' (+) imported xs
| ```
|
| As you see it has a top-level exported thing (mysum). My problem is that
| I'm traversing the type-checked AST (i.e. returned by `typecheckedSource
| module`) trying to collect all the names so I can index them for a code
| search project I'm working on. It's a bit similar to the GHC ctags/etags
| tool, except I'm trying to index all the source code.
|
| So for every Name I run into in the source code I need to figure out
| what kind of name it is. That's made quite tricky by the fact that name
| resolution isn't actually quite done by the time we have the typed AST
| (i.e. mysum ought to have the name "Test.mysum", but it has the name
| "mysum"). I can try to implement this last resolution step myself, but
| then I need to understand how to identify names such as mysum above,
| while traversing the AST.
|
| -- Johan
More information about the ghc-devs
mailing list