A couple of GHC-API questions

Simon Peyton Jones simonpj at microsoft.com
Thu Jul 24 22:54:05 UTC 2014


| This is what I mean by “resolving” the types. For single-module programs
| this is trivial, we can do something like
| 
|     resolve x = do rn <- hscParseIdentifier x
|                    hscTcRnLookupRdrName rn
| 
| For multi-module programs it becomes trickier because we also have to
| resolve the types that we’ve imported from other modules. 

No, that is no harder **provided those types are in scope**.  So suppose you have

   module M where
     import A( Foo )
     f :: Int -> Int
     {-# LIQUID f :: { x | ..blah..Foo..blah } -> Int #-}

Here I am supposing that the Liquid Haskell specification is in a pragma of M, and mentions an imported data type Foo.

To resolve the string "Foo" to the Name A.Foo (or Bar.Foo, or whatever), hscTcRnLookupRdrName will work just fine.

If you import Foo qualified, then of course you'll have to use a qualified name in the source
 
   module M where
     import qualified A( Foo )
     f :: Int -> Int
     {-# LIQUID f :: { x | ..blah..A.Foo..blah } -> Int #-}

If you *don't* import Foo at all, then it's utterly non-obvious where to look for it, so I don't suppose you are doing that.

In short, why doesn’t hscTcRnLookupRdrName do the job?

Incidentally, it doesn't make sense to ask if a Name is "in scope".  Only RdrNames can be "in scope" or "not in scope".

Simon


| example from earlier, when we type-check module B we have to turn the
| String “Foo” into the Name A.Foo. This is problematic because module B
| imported module A qualified, so “Foo” is not in scope inside B but
| “A.Foo” is.
| 
| I believe GHC might be avoiding this issue via the .hi files, so when you
| import a Type from another module, it is already using TyCons instead of
| Strings.
| 
| > Later you say "is there a simple way to ask GHC to resolve the name x
| in the context of module
| > m". You could mean
| > * Imagine that the unqualified name "x" appeared in module m. How do I
| look it up, in m's
| > top-level lexical environment.
| > but I don’t think that is what you mean.
| 
| I think this is almost exactly what I mean, except that I want to be able
| to look up the unqualified “x” as well as the qualified
| “SomeModuleThatMayHaveBeenRenamed.x” inside m’s top-level environment.
| This is more or less what the
| DynamicLoading.lookupRdrNameInModuleForPlugins function that I’ve copied
| and tweaked does, but it requires the presence of the original source
| code. I’m hoping there may be some other function out there that does the
| same thing without requiring the source code, so we can use it for the
| base libraries as well.
| 
| > I'm confused. Could you be more concrete?
| > Possibly this may help?
| https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/NameType
| 
| Thanks for the reference, I’m familiar with most of the info there
| already from browsing GHC’s source, but this is laid out much more
| newcomer-friendly manner :)
| 
| Hopefully I’ve made my question a bit clearer.
| 
| Eric


More information about the ghc-devs mailing list