<div dir="ltr">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)<div><br></div><div><a href="http://llvm.org/docs/CommandGuide/llvm-link.html">http://llvm.org/docs/CommandGuide/llvm-link.html</a> </div><div><br></div><div>Here's some example code:</div><div><br></div><div><div>-- Main.hs --</div><div><br></div><div>{-# LANGUAGE MagicHash #-}</div><div>{-# LANGUAGE UnboxedTuples #-}</div><div>{-# LANGUAGE GHCForeignImportPrim #-}</div><div>{-# LANGUAGE ForeignFunctionInterface #-}</div><div>{-# LANGUAGE UnliftedFFITypes #-}</div><div>{-# LANGUAGE BangPatterns #-}</div><div><br></div><div>import GHC.Exts(Word(W#))</div><div>import GHC.Prim(Word#)</div><div><br></div><div>foreign import ccall llvmid :: Word# -> Word#</div><div><br></div><div>main = do</div><div>  line1 <- getLine</div><div>  let !(W# x1) = read line1</div><div>  let !r1 = llvminc x1</div><div>  print (W# r1)</div><div><br></div><div><br></div><div>-- funcs.ll --</div><div><br></div><div>define fastcc i64 @llvminc(i64 inreg %x) {</div><div>  %r = add i64 %x, 1</div><div>  ret i64 %r</div><div>}</div></div><div><br></div><div>When I compile like the following:</div><div><br></div><div><div>ghc -O2 -fllvm -keep-s-files Main.hs funcs.ll</div></div><div><br></div><div>I get an executable that performs correctly, but when I look at the assembly output in Main.s I get the following:</div><div><br></div><div><div><span class="" style="white-space:pre"> </span>callq<span class="" style="white-space:pre">     </span>suspendThread</div><div><span class="" style="white-space:pre">      </span>movq<span class="" style="white-space:pre">      </span>%rax, %rbp</div><div><span class="" style="white-space:pre"> </span>movq<span class="" style="white-space:pre">      </span>%rbx, %rdi</div><div><span class="" style="white-space:pre"> </span>callq<span class="" style="white-space:pre">     </span>llvminc</div><div><span class="" style="white-space:pre">    </span>movq<span class="" style="white-space:pre">      </span>%rax, %rbx</div><div><span class="" style="white-space:pre"> </span>movq<span class="" style="white-space:pre">      </span>%rbp, %rdi</div><div><span class="" style="white-space:pre"> </span>callq<span class="" style="white-space:pre">     </span>resumeThread</div></div><div><br></div><div>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.</div><div><br></div><div>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?</div></div>