[Haskell-cafe] Running GHC LLVM output through LLVM bitcode linker first

Clinton Mead clintonmead at gmail.com
Mon Nov 23 03:15:05 UTC 2015


Is there a way to run the LLVM code (both generated by Haskell and provided
by the user) though the LLVM bitcode linker to perform intermodule
optimizations (like inlining)

http://llvm.org/docs/CommandGuide/llvm-link.html

Here's some example code:

-- Main.hs --

{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE BangPatterns #-}

import GHC.Exts(Word(W#))
import GHC.Prim(Word#)

foreign import ccall llvmid :: Word# -> Word#

main = do
  line1 <- getLine
  let !(W# x1) = read line1
  let !r1 = llvminc x1
  print (W# r1)


-- funcs.ll --

define fastcc i64 @llvminc(i64 inreg %x) {
  %r = add i64 %x, 1
  ret i64 %r
}

When I compile like the following:

ghc -O2 -fllvm -keep-s-files Main.hs funcs.ll

I get an executable that performs correctly, but when I look at the
assembly output in Main.s I get the following:

callq suspendThread
movq %rax, %rbp
movq %rbx, %rdi
callq llvminc
movq %rax, %rbx
movq %rbp, %rdi
callq resumeThread

This leads me to believe that this is being done like a c call through
registers, but not inlined, though I'm not sure about this. I also suspect
sending the "Main.ll" and "funcs.ll" files through the LLVM bitcode linker
and then sending the resulting one bitcode to the LLVM compiler would
perform these intramodule optimisations.

Is there anyway to get GHC to use the LLVM bitcode linker to link all the
LLVM files (both user provided and resulting from GHC compilation) though
the LLVM bitcode linker first before the system linker?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20151123/f6f1570f/attachment.html>


More information about the Haskell-Cafe mailing list