Running GHC LLVM output through LLVM bitcode linker first

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?

Clinton Mead
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#
Are you sure this code compiled? The above should read `llvminc`. Moreover, if you really want this call to be efficient you should mark it as unsafe [1]. This will eliminate the `suspendThread`/`resumeThread` calls, which add significant cost. After doing this is appears that the call is only one extra `movq`, movq 7(%rbx), %rdi callq llvminc
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?
In general I'm not sure that this would be safe. In particular, GHC's calling convention is much different than that expected by LLVM's link-time optimizer and while `llvminc` would be safe to inline here (as it's a ccall), I'm not sure that this is the case in general. What are you trying to do that requires such optimal code generation? If you want to put a call like this in an inner loop you'd likely be better off either writing the entire loop in LLVM or adding a new primop to GHC. Cheers, - Ben
participants (2)
-
Ben Gamari
-
Clinton Mead