Writing a simple Core evaluator, having trouble with name lookups

Csaba Hruska csaba.hruska at gmail.com
Fri Nov 30 08:17:59 UTC 2018


Hi!

I can give some info for your second question.
GHC uses wired-in id's for the primitives and some other AST construction
too.
Read more here:
https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/WiredIn

Regarding the names you can use qualified (module + occ) names for exported
ids. (see: *Var.isExportedId*).
For non exported Id's you can rely on unique values.
Use the *Name.nameModule_maybe* and *Name.getName* function to get the id's
module name.

In my project I export STG for further compilation. Here is the conversion
code with proper name conversion:
https://github.com/grin-tech/ghc-grin/blob/master/ghc-dump-core/GhcDump_StgConvert.hs

I've also learned that GHC wraps the* Main.main* function with another
function called *:Main.main* which is the first function called by the RTS.

Cheers,
Csaba


On Tue, Nov 27, 2018 at 7:00 PM Christopher Done <chrisdone at gmail.com>
wrote:

> Hi all,
>
> I'm attempting to make a simple evaluator for GHC core, but I'm not
> clear on how to reliably looking up names. I'm compiling each of
> ghc-prim, integer-simple and base with a patched version of GHC which
> performs an extra output step with the Core AST to a file for each
> module.
>
> Later, I load those files in. So for an input Haskell file like this:
>
>     module Main (main,Foo(..)) where
>     class Foo a where foo :: a -> Int
>     instance Foo Int where foo x = x * x
>     instance Foo Char where foo x = 99
>     main = print (foo (123 :: Int))
>
> I have an output set of bindings like this:
>
> https://gist.github.com/chrisdone/cb05a77d3fcb081a4580b5f85289674a
>
> One thing that I immediately notice is that the names of things are
> completely non-unique, especially in generated names. So here are two
> implementations of the method "foo" for the class "Foo":
>
> ( Id {idStableName = "main:Main:$cfoo", idUnique = Unique
> 6989586621679010917}, ...) -- Int
> ( Id {idStableName = "main:Main:$cfoo", idUnique = Unique
> 6989586621679010923}, ...) -- Char
>
> So e.g. the instance for "Foo Int" refers to the above method
> implementation via its Unique (6989586621679010923):
>
> ( Id
>     {idStableName = "main:Main:$fFooInt", idUnique = Unique
> 8214565720323784705}
> , CastE
>     (VarE
>        (Id
>           { idStableName = "main:Main:$cfoo"
>           , idUnique = Unique 6989586621679010923 <---- HERE
>           })))
>
> At first, I thought I would use the Unique associated with every Name to
> make a lookup. This is completely reliable within one GHC compilation,
> but I've read in the docs that it's not stable across multiple
> invocations? What does that mean for my case?
>
> Another thing I notice is that type-class methods are not generated at
> the core level. I have, for example, this method call that provides it
> the instance dictionary,
>
>     (AppE
>        (AppE
>           (VarE
>              (Id
>                 { idStableName = "main:Main:foo"
>                 , idUnique = Unique 8214565720323784707 <---- MISSING
>                 }))
>           (TypE (Typ "Int")))
>        (VarE
>           (Id
>              { idStableName = "main:Main:$fFooInt"
>              , idUnique = Unique 8214565720323784705
>              })))
>
> But the "main:Main:foo" (8214565720323784707) is not produced in the
> CoreProgram, it seems. My compile step is very simple:
>
>     compile ::
>          GHC.GhcMonad m
>       => GHC.ModSummary
>       -> m [CoreSyn.Bind GHC.Var]
>     compile modSummary = do
>       parsedModule <- GHC.parseModule modSummary
>       typecheckedModule <- GHC.typecheckModule parsedModule
>       desugared <- GHC.desugarModule typecheckedModule
>       let binds = GHC.mg_binds (GHC.dm_core_module desugared)
>       pure binds
>
> It simply gets the bindings and that's all from the ModGuts.
>
>     mg_binds :: !CoreProgram
>
> Two questions:
>
> 1) How do I recognize class methods when I see one, like the
>    "main:Main:foo" above?
>
>    Maybe this? isClassOpId_maybe :: Id -> Maybe Class
>
>    Is an "op" what GHC calls type-class methods?
>
> 2) If I compile e.g. ghc-prim and that generates a binding Name with ID
>    123, and then I compile base -- will the ID 123 be re-used by base
>    for something else, or will any reference to 123 in the compiled
>    Names for base refer ONLY to that one in ghc-prim? In other words,
>    when GHC loads the iface for ghc-prim, does it generate a fresh set
>    of names for everything in ghc-prim, or does it load them from file?
>
> Cheers!
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20181130/49aa0b8b/attachment-0001.html>


More information about the ghc-devs mailing list