fa72b7f
From 834644b81c536fc81022a0a13f860fb33e3d78d2 Mon Sep 17 00:00:00 2001
c4dd5fe
From: "Richard W.M. Jones" <rjones@redhat.com>
c4dd5fe
Date: Fri, 24 Oct 2014 12:59:23 +0200
c4dd5fe
Subject: [PATCH 07/15] ppc64: Update for OCaml 4.02.0.
c4dd5fe
c4dd5fe
These are based on the power (ppc32) branch and some guesswork.
c4dd5fe
In particular, I'm not convinced that my changes to floating
c4dd5fe
point constant handling are correct, although I wrote a small
c4dd5fe
test program which worked.
c4dd5fe
c4dd5fe
Therefore these are not yet integrated into the main patch.
c4dd5fe
---
c4dd5fe
 asmcomp/power64/CSE.ml        | 37 +++++++++++++++++++++++++++++++++++++
c4dd5fe
 asmcomp/power64/emit.mlp      | 23 ++++++++++++++---------
c4dd5fe
 asmcomp/power64/proc.ml       |  8 ++++----
c4dd5fe
 asmcomp/power64/scheduling.ml |  2 +-
c4dd5fe
 4 files changed, 56 insertions(+), 14 deletions(-)
c4dd5fe
 create mode 100644 asmcomp/power64/CSE.ml
c4dd5fe
c4dd5fe
diff --git a/asmcomp/power64/CSE.ml b/asmcomp/power64/CSE.ml
c4dd5fe
new file mode 100644
c4dd5fe
index 0000000..ec10d2d
c4dd5fe
--- /dev/null
c4dd5fe
+++ b/asmcomp/power64/CSE.ml
c4dd5fe
@@ -0,0 +1,37 @@
c4dd5fe
+(***********************************************************************)
c4dd5fe
+(*                                                                     *)
c4dd5fe
+(*                                OCaml                                *)
c4dd5fe
+(*                                                                     *)
c4dd5fe
+(*            Xavier Leroy, projet Gallium, INRIA Rocquencourt         *)
c4dd5fe
+(*                                                                     *)
c4dd5fe
+(*  Copyright 2014 Institut National de Recherche en Informatique et   *)
c4dd5fe
+(*  en Automatique.  All rights reserved.  This file is distributed    *)
c4dd5fe
+(*  under the terms of the Q Public License version 1.0.               *)
c4dd5fe
+(*                                                                     *)
c4dd5fe
+(***********************************************************************)
c4dd5fe
+
c4dd5fe
+(* CSE for the PowerPC *)
c4dd5fe
+
c4dd5fe
+open Arch
c4dd5fe
+open Mach
c4dd5fe
+open CSEgen
c4dd5fe
+
c4dd5fe
+class cse = object (self)
c4dd5fe
+
c4dd5fe
+inherit cse_generic as super
c4dd5fe
+
c4dd5fe
+method! class_of_operation op =
c4dd5fe
+  match op with
c4dd5fe
+  | Ispecific(Imultaddf | Imultsubf) -> Op_pure
c4dd5fe
+  | Ispecific(Ialloc_far _) -> Op_other
c4dd5fe
+  | _ -> super#class_of_operation op
c4dd5fe
+
c4dd5fe
+method! is_cheap_operation op =
c4dd5fe
+  match op with
c4dd5fe
+  | Iconst_int n | Iconst_blockheader n -> n <= 32767n && n >= -32768n
c4dd5fe
+  | _ -> false
c4dd5fe
+
c4dd5fe
+end
c4dd5fe
+
c4dd5fe
+let fundecl f =
c4dd5fe
+  (new cse)#fundecl f
c4dd5fe
diff --git a/asmcomp/power64/emit.mlp b/asmcomp/power64/emit.mlp
c4dd5fe
index d84ac5c..9fd59b2 100644
c4dd5fe
--- a/asmcomp/power64/emit.mlp
c4dd5fe
+++ b/asmcomp/power64/emit.mlp
c4dd5fe
@@ -292,6 +292,7 @@ let name_for_int_comparison = function
c4dd5fe
 let name_for_intop = function
c4dd5fe
     Iadd -> "add"
c4dd5fe
   | Imul -> "mulld"
c4dd5fe
+  | Imulh -> "mulhd"
c4dd5fe
   | Idiv -> "divd"
c4dd5fe
   | Iand -> "and"
c4dd5fe
   | Ior  -> "or"
c4dd5fe
@@ -354,7 +355,8 @@ let load_store_size = function
c4dd5fe
 let instr_size = function
c4dd5fe
     Lend -> 0
c4dd5fe
   | Lop(Imove | Ispill | Ireload) -> 1
c4dd5fe
-  | Lop(Iconst_int n) -> if is_native_immediate n then 1 else 2
c4dd5fe
+  | Lop(Iconst_int n | Iconst_blockheader n) ->
c4dd5fe
+    if is_native_immediate n then 1 else 2
c4dd5fe
   | Lop(Iconst_float s) -> 2
c4dd5fe
   | Lop(Iconst_symbol s) -> 2
c4dd5fe
   | Lop(Icall_ind) -> 6
c4dd5fe
@@ -370,7 +372,7 @@ let instr_size = function
c4dd5fe
       if chunk = Byte_signed
c4dd5fe
       then load_store_size addr + 1
c4dd5fe
       else load_store_size addr
c4dd5fe
-  | Lop(Istore(chunk, addr)) -> load_store_size addr
c4dd5fe
+  | Lop(Istore(chunk, addr, _)) -> load_store_size addr
c4dd5fe
   | Lop(Ialloc n) -> 4
c4dd5fe
   | Lop(Ispecific(Ialloc_far n)) -> 5
c4dd5fe
   | Lop(Iintop Imod) -> 3
c4dd5fe
@@ -397,7 +399,7 @@ let instr_size = function
c4dd5fe
   | Lsetuptrap lbl -> 1
c4dd5fe
   | Lpushtrap -> 7
c4dd5fe
   | Lpoptrap -> 1
c4dd5fe
-  | Lraise -> 6
c4dd5fe
+  | Lraise _ -> 6
c4dd5fe
 
c4dd5fe
 let label_map code =
c4dd5fe
   let map = Hashtbl.create 37 in
c4dd5fe
@@ -492,7 +494,7 @@ let rec emit_instr i dslot =
c4dd5fe
             | (_, _) ->
c4dd5fe
                 fatal_error "Emit: Imove"
c4dd5fe
         end
c4dd5fe
-    | Lop(Iconst_int n) ->
c4dd5fe
+    | Lop(Iconst_int n | Iconst_blockheader n) ->
c4dd5fe
         if is_native_immediate n then
c4dd5fe
           `    li      {emit_reg i.res.(0)}, {emit_nativeint n}\n`
c4dd5fe
         else if n >= -0x8000_0000n && n <= 0x7FFF_FFFFn then begin
c4dd5fe
@@ -502,7 +504,8 @@ let rec emit_instr i dslot =
c4dd5fe
         end else begin
c4dd5fe
            `   ld      {emit_reg i.res.(0)}, {emit_tocref (TocInt n)}\n`
c4dd5fe
         end
c4dd5fe
-    | Lop(Iconst_float s) ->
c4dd5fe
+    | Lop(Iconst_float f) ->
c4dd5fe
+        let s = string_of_float f in
c4dd5fe
         `      lfd     {emit_reg i.res.(0)}, {emit_tocref (TocFloat s)}\n`
c4dd5fe
     | Lop(Iconst_symbol s) ->
c4dd5fe
         `      ld      {emit_reg i.res.(0)}, {emit_tocref (TocSymOfs (s,0))}\n`
c4dd5fe
@@ -581,7 +584,7 @@ let rec emit_instr i dslot =
c4dd5fe
         emit_load_store loadinstr addr i.arg 0 i.res.(0);
c4dd5fe
         if chunk = Byte_signed then
c4dd5fe
           `    extsb   {emit_reg i.res.(0)}, {emit_reg i.res.(0)}\n`
c4dd5fe
-    | Lop(Istore(chunk, addr)) ->
c4dd5fe
+    | Lop(Istore(chunk, addr, _)) ->
c4dd5fe
         let storeinstr =
c4dd5fe
           match chunk with
c4dd5fe
             Byte_unsigned | Byte_signed -> "stb"
c4dd5fe
@@ -772,7 +775,7 @@ let rec emit_instr i dslot =
c4dd5fe
        `       mr      {emit_gpr 29}, {emit_gpr 11}\n`
c4dd5fe
     | Lpoptrap ->
c4dd5fe
         `      ld      {emit_gpr 29}, 0({emit_gpr 29})\n`
c4dd5fe
-    | Lraise ->
c4dd5fe
+    | Lraise _ ->
c4dd5fe
         `      ld      {emit_gpr 0}, 8({emit_gpr 29})\n`;
c4dd5fe
         `      ld      {emit_gpr 1}, 16({emit_gpr 29})\n`;
c4dd5fe
         `      ld      {emit_gpr 2}, 24({emit_gpr 29})\n`;
c4dd5fe
@@ -903,9 +906,11 @@ let emit_item = function
c4dd5fe
   | Cint n ->
c4dd5fe
       `        .quad   {emit_nativeint n}\n`
c4dd5fe
   | Csingle f ->
c4dd5fe
-      `        .float  0d{emit_string f}\n`
c4dd5fe
+      let s = string_of_float f in
c4dd5fe
+      `        .float  0d{emit_string s}\n`
c4dd5fe
   | Cdouble f ->
c4dd5fe
-      `        .double 0d{emit_string f}\n`
c4dd5fe
+      let s = string_of_float f in
c4dd5fe
+      `        .double 0d{emit_string s}\n`
c4dd5fe
   | Csymbol_address s ->
c4dd5fe
       `        .quad   {emit_symbol s}\n`
c4dd5fe
   | Clabel_address lbl ->
c4dd5fe
diff --git a/asmcomp/power64/proc.ml b/asmcomp/power64/proc.ml
c4dd5fe
index 372303d..a5a35f3 100644
c4dd5fe
--- a/asmcomp/power64/proc.ml
c4dd5fe
+++ b/asmcomp/power64/proc.ml
c4dd5fe
@@ -85,11 +85,11 @@ let rotate_registers = true
c4dd5fe
 (* Representation of hard registers by pseudo-registers *)
c4dd5fe
 
c4dd5fe
 let hard_int_reg =
c4dd5fe
-  let v = Array.create 23 Reg.dummy in
c4dd5fe
+  let v = Array.make 23 Reg.dummy in
c4dd5fe
   for i = 0 to 22 do v.(i) <- Reg.at_location Int (Reg i) done; v
c4dd5fe
 
c4dd5fe
 let hard_float_reg =
c4dd5fe
-  let v = Array.create 31 Reg.dummy in
c4dd5fe
+  let v = Array.make 31 Reg.dummy in
c4dd5fe
   for i = 0 to 30 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done; v
c4dd5fe
 
c4dd5fe
 let all_phys_regs =
c4dd5fe
@@ -105,7 +105,7 @@ let stack_slot slot ty =
c4dd5fe
 
c4dd5fe
 let calling_conventions
c4dd5fe
     first_int last_int first_float last_float make_stack stack_ofs arg =
c4dd5fe
-  let loc = Array.create (Array.length arg) Reg.dummy in
c4dd5fe
+  let loc = Array.make (Array.length arg) Reg.dummy in
c4dd5fe
   let int = ref first_int in
c4dd5fe
   let float = ref first_float in
c4dd5fe
   let ofs = ref stack_ofs in
c4dd5fe
@@ -159,7 +159,7 @@ let loc_results res =
c4dd5fe
 
c4dd5fe
 let poweropen_external_conventions first_int last_int
c4dd5fe
                                    first_float last_float arg =
c4dd5fe
-  let loc = Array.create (Array.length arg) Reg.dummy in
c4dd5fe
+  let loc = Array.make (Array.length arg) Reg.dummy in
c4dd5fe
   let int = ref first_int in
c4dd5fe
   let float = ref first_float in
c4dd5fe
   let ofs = ref (14 * size_addr) in
c4dd5fe
diff --git a/asmcomp/power64/scheduling.ml b/asmcomp/power64/scheduling.ml
c4dd5fe
index b7bba9b..b582b6a 100644
c4dd5fe
--- a/asmcomp/power64/scheduling.ml
c4dd5fe
+++ b/asmcomp/power64/scheduling.ml
c4dd5fe
@@ -46,7 +46,7 @@ method reload_retaddr_latency = 12
c4dd5fe
 method oper_issue_cycles = function
c4dd5fe
     Iconst_float _ | Iconst_symbol _ -> 2
c4dd5fe
   | Iload(_, Ibased(_, _)) -> 2
c4dd5fe
-  | Istore(_, Ibased(_, _)) -> 2
c4dd5fe
+  | Istore(_, Ibased(_, _), _) -> 2
c4dd5fe
   | Ialloc _ -> 4
c4dd5fe
   | Iintop(Imod) -> 40 (* assuming full stall *)
c4dd5fe
   | Iintop(Icomp _) -> 4
c4dd5fe
-- 
4c52516
2.3.1
c4dd5fe