-prof -fPIC -fexternal-dynamic-refs generates non-PIC relocations for external symbol
When compiling code with -prof -fPIC -fexternal-dynamic-refs
, the generated object file may contains R_X86_64_PC32 relocation to symbols defined in another object file.
$ cat T15723A.hs T15723B.hs
module T15723A where
{-# INLINE foo #-}
foo :: Int -> Int
foo x = {-# SCC foo1 #-} bar x
{-# NOINLINE bar #-}
bar :: Int -> Int
bar x = x
module T15723B where
import T15723A
test :: Int -> Int
test x = {-# SCC test1 #-} foo $ foo x
$ $HC -prof -prof -fPIC -fexternal-dynamic-refs -O2 -c T15723A.hs
$ $HC -prof -prof -fPIC -fexternal-dynamic-refs -O2 -c T15723B.hs
$ objdump -rdS T15723B.o | less
0000000000000028 <T15723B_test_info>:
28: 48 8d 45 f0 lea -0x10(%rbp),%rax
2c: 4c 39 f8 cmp %r15,%rax
2f: 72 70 jb a1 <T15723B_test_info+0x79>
31: 48 83 ec 08 sub $0x8,%rsp
35: 48 8d 35 00 00 00 00 lea 0x0(%rip),%rsi # 3c <T15723B_test_info+0x14>
38: R_X86_64_PC32 T15723B_test1_EXPR_cc-0x4
3c: 49 8b bd 60 03 00 00 mov 0x360(%r13),%rdi
43: 31 c0 xor %eax,%eax
45: e8 00 00 00 00 callq 4a <T15723B_test_info+0x22>
46: R_X86_64_PLT32 pushCostCentre-0x4
4a: 48 83 c4 08 add $0x8,%rsp
4e: 48 ff 40 30 incq 0x30(%rax)
52: 49 89 85 60 03 00 00 mov %rax,0x360(%r13)
59: 48 83 ec 08 sub $0x8,%rsp
5d: 48 8d 35 00 00 00 00 lea 0x0(%rip),%rsi # 64 <T15723B_test_info+0x3c>
60: R_X86_64_PC32 T15723A_foo1_EXPR_cc-0x4
When attempt to link both T15723A.o
and T15723B.o
in ghci using +RTS -xp
, the address of T15723A_foo1_EXPR_cc
can be more than 2G away from T15723B_test_info
and cause link error or segfault.