Why do Names defined in the current module lack a module name?

Manuel M T Chakravarty chak at cse.unsw.edu.au
Thu Apr 4 02:42:45 CEST 2013


Johan Tibell <johan.tibell at gmail.com>:
> On Wed, Apr 3, 2013 at 5:14 AM, Simon Peyton-Jones
> <simonpj at microsoft.com> wrote:
>> 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
> I'm not dumping the names using a command line flag, but using a
> program that uses the GHC API that I wrote. 

Simon's point is that GHC can print names in different ways. The verbosity of a printed name depends on the context in which it is printed (and -dppr-debug is a way to tell GHC that you want to get all info, including uniques etc).

> This is how I use the GHC
> API to get hold of the AST once the source code has been compiled:
> 
> forEachM z xs f = foldM f z xs
> 
> indexSymbols :: ModuleGraph -> Ghc Builder.Builder
> indexSymbols graph = forEachM Builder.new graph $ \ builder ms -> do
>    let filename = msHsFilePath ms
>    handleSourceError printErrorAndExit $ do
>        liftIO $ putStrLn ("Loading " ++ filename ++ " ...")
>        mod <- loadModule =<< typecheckModule =<< parseModule ms
>        case mod of
>            _ | isBootSummary ms -> return builder
>            _ | Just (group, _, _, _) <- renamedSource mod -> do
>                let modname = moduleName $ ms_mod ms
>                    builder' = invertedIndex builder modname $ bagToList $
>                               symbols group (typecheckedSource mod)
> -- ** HERE **
>                liftIO $ print $ builder'
>                return $! builder'
>            _  -> liftIO $ exitWith (ExitFailure 1)
>  where
>    printErrorAndExit e = do
>        printException e
>        liftIO $ exitWith (ExitFailure 1)
> 
> So I invoke my AST traversal function 'symbols' (which just extracts
> all the Names in the AST into a Bag) on the AST returned by
> 'typecheckedSource mod'. This is the AST I expected to have fully
> qualified names but doesn't.

I'm not sure what your 'invertedIndex' does. You seem to use the 'Show' instance via 'print'. However, I don't think 'Name' has a 'Show' instance. So, I wonder how you convert the 'Name's to 'String's.

In GHC, we do the following, use 'ppr' to convert an entity to an 'SDoc' and then when the 'SDoc' gets turned into a 'String', the dynamic flags determine what detail of a 'Name' to print. You can do this in one step with 'showPpr' <http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-7.6.2/Outputable.html#v:showPpr>, but you need to supply some 'DynFlags' <http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-7.6.2/DynFlags.html#t:DynFlags>.

Manuel




More information about the ghc-devs mailing list