Blob Blame History Raw
From c428a156b8e659a884d4867e52c49534125dc72f Mon Sep 17 00:00:00 2001
From: Mark Shinwell <mshinwell@gmail.com>
Date: Wed, 13 Sep 2017 10:23:16 +0100
Subject: [PATCH 12/12] AArch64 GOT fixed

---
 Changes                    |  4 ++++
 asmcomp/arm64/emit.mlp     | 15 +++++++++++++--
 asmcomp/arm64/selection.ml |  4 ++--
 3 files changed, 19 insertions(+), 4 deletions(-)

diff --git a/Changes b/Changes
index e8dbd42e2..b84a1f30e 100644
--- a/Changes
+++ b/Changes
@@ -150,6 +150,10 @@ OCaml 4.05.0 (13 Jul 2017):
   (Hannes Mehnert, Guillaume Bury,
    review by Daniel Bünzli, Gabriel Scherer, Damien Doligez)
 
+- GPR#1330: when generating dynamically-linkable code on AArch64, always
+  reference symbols (even locally-defined ones) through the GOT.
+  (Mark Shinwell, review by Xavier Leroy)
+
 ### Standard library:
 
 - MPR#6975, GPR#902: Truncate function added to stdlib Buffer module
diff --git a/asmcomp/arm64/emit.mlp b/asmcomp/arm64/emit.mlp
index f75646e12..729096c57 100644
--- a/asmcomp/arm64/emit.mlp
+++ b/asmcomp/arm64/emit.mlp
@@ -114,6 +114,7 @@ let emit_addressing addr r =
   | Iindexed ofs ->
       `[{emit_reg r}, #{emit_int ofs}]`
   | Ibased(s, ofs) ->
+      assert (not !Clflags.dlcode);  (* see selection.ml *)
       `[{emit_reg r}, #:lo12:{emit_symbol_offset s ofs}]`
 
 (* Record live pointers at call points *)
@@ -323,7 +324,7 @@ let emit_literals() =
 (* Emit code to load the address of a symbol *)
 
 let emit_load_symbol_addr dst s =
-  if (not !Clflags.dlcode) || Compilenv.symbol_in_current_unit s then begin
+  if not !Clflags.dlcode then begin
     `	adrp	{emit_reg dst}, {emit_symbol s}\n`;
     `	add	{emit_reg dst}, {emit_reg dst}, #:lo12:{emit_symbol s}\n`
   end else begin
@@ -609,6 +610,7 @@ let emit_instr i =
           match addr with
           | Iindexed _ -> i.arg.(0)
           | Ibased(s, ofs) ->
+              assert (not !Clflags.dlcode);  (* see selection.ml *)
               `	adrp	{emit_reg reg_tmp1}, {emit_symbol_offset s ofs}\n`;
               reg_tmp1 in
         begin match size with
@@ -636,6 +638,7 @@ let emit_instr i =
           match addr with
           | Iindexed _ -> i.arg.(1)
           | Ibased(s, ofs) ->
+              assert (not !Clflags.dlcode);
               `	adrp	{emit_reg reg_tmp1}, {emit_symbol_offset s ofs}\n`;
               reg_tmp1 in
         begin match size with
@@ -924,7 +927,15 @@ let fundecl fundecl =
 
 let emit_item = function
   | Cglobal_symbol s -> `	.globl	{emit_symbol s}\n`;
-  | Cdefine_symbol s -> `{emit_symbol s}:\n`
+  | Cdefine_symbol s ->
+    if !Clflags.dlcode then begin
+      (* GOT relocations against non-global symbols don't seem to work
+         properly: GOT entries are not created for the symbols and the
+         relocations evaluate to random other GOT entries.  For the moment
+         force all symbols to be global. *)
+      `	.globl	{emit_symbol s}\n`;
+    end;
+    `{emit_symbol s}:\n`
   | Cint8 n -> `	.byte	{emit_int n}\n`
   | Cint16 n -> `	.short	{emit_int n}\n`
   | Cint32 n -> `	.long	{emit_nativeint n}\n`
diff --git a/asmcomp/arm64/selection.ml b/asmcomp/arm64/selection.ml
index d8ea7f83b..b714d0032 100644
--- a/asmcomp/arm64/selection.ml
+++ b/asmcomp/arm64/selection.ml
@@ -82,8 +82,8 @@ let inline_ops =
   [ "sqrt"; "caml_bswap16_direct"; "caml_int32_direct_bswap";
     "caml_int64_direct_bswap"; "caml_nativeint_direct_bswap" ]
 
-let use_direct_addressing symb =
-  (not !Clflags.dlcode) || Compilenv.symbol_in_current_unit symb
+let use_direct_addressing _symb =
+  not !Clflags.dlcode
 
 (* Instruction selection *)
 
-- 
2.13.2