GHC API: Access to nativeCodeGen?

Donald Bruce Stewart dons at cse.unsw.edu.au
Mon Jul 4 03:43:22 EDT 2005


dons:
> pj:
> > Hello,
> > 
> > I would like to use nativeCodeGen outside of GHC to generate code from
> > an IR. The IR would be produced by a third party program, not the GHC
> > frontend. 
> > 
> > Looking at CVS HEAD I can see that GHC.hs exports plenty of things
> > (for the GHC API I presume), but I can't find anything that lets me
> > input some sort of IR and have ASM in return. Am I missing it
> > somewhere or is there no way to input IR and get ASM in return? If
> > there isn't, is such a feature planned/wanted?
> > 
> > If such a feature isn't planned, I would appreciate any ideas on how
> > to to accomplish the same thing. I have no problems with having a
> > build tree of GHC laying around if that makes things easier. It would
> > be a nice bonus if it made my maintenance burden low.
> 
> You could use External Core with GHC, couldn't you?

For example:

Your src:
    $ cat M.hs
    module M where

    f = "foo"

Compile to Core:
    $ ghc -fno-code -fext-core M.hs

Now edit M.hcr.

And compile that to assembly:
    $ ghc -fasm -c -keep-tmp-files M.hcr

And inspect your piping-hot asm ...
    $ cat ghc17508.s 
    .data
            .align 4
    _module_registered:
            .long   0

    .text
            .align 4,0x90
    .globl __stginit_M_
    __stginit_M_:
            cmpl $0,_module_registered
            jne .Lc5Y
    .Lc5Z:
            movl $1,_module_registered
    .Lc5Y:
            addl $4,%ebp
            jmp *-4(%ebp)

    .text
            .align 4,0x90
    .globl __stginit_M
    __stginit_M:
            jmp __stginit_M_

-- Don


More information about the Glasgow-haskell-users mailing list