More fixes for ppc64/ppc64le (RHBZ#1156300).
This commit is contained in:
parent
a7ead0bb4e
commit
c4dd5fe841
@ -1,7 +1,7 @@
|
||||
From ccc1bf226619608230dc94b26377756719cf7b20 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 24 Jun 2014 22:29:38 +0100
|
||||
Subject: [PATCH 01/13] Don't ignore ./configure, it's a real git file.
|
||||
Subject: [PATCH 01/15] Don't ignore ./configure, it's a real git file.
|
||||
|
||||
---
|
||||
.gitignore | 1 -
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 0e3b6450f6ab803442a809b6da41d5d5c5da650f Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Thu, 7 Jun 2012 15:36:16 +0100
|
||||
Subject: [PATCH 02/13] Ensure empty compilerlibs/ directory is created by git.
|
||||
Subject: [PATCH 02/15] Ensure empty compilerlibs/ directory is created by git.
|
||||
|
||||
This directory exists in the OCaml tarball, but is empty. As a
|
||||
result, git ignores it unless we put a dummy file in it.
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 79f0f91e3e4abbfbd3564c11ea72e53310236afc Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 24 Jun 2014 10:00:15 +0100
|
||||
Subject: [PATCH 03/13] Don't add rpaths to libraries.
|
||||
Subject: [PATCH 03/15] Don't add rpaths to libraries.
|
||||
|
||||
---
|
||||
tools/Makefile.shared | 6 +++---
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 11b377aee2811891635982a5590fef62f12645b6 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 29 May 2012 20:40:36 +0100
|
||||
Subject: [PATCH 04/13] ocamlbyteinfo, ocamlplugininfo: Useful utilities from
|
||||
Subject: [PATCH 04/15] ocamlbyteinfo, ocamlplugininfo: Useful utilities from
|
||||
Debian, sent upstream.
|
||||
|
||||
See:
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 5308c47681201ef3beef3e543ab877f81aa08784 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 29 May 2012 20:44:18 +0100
|
||||
Subject: [PATCH 05/13] configure: Allow user defined C compiler flags.
|
||||
Subject: [PATCH 05/15] configure: Allow user defined C compiler flags.
|
||||
|
||||
---
|
||||
configure | 4 ++++
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 3628c89d319ac8286b62ec1405561b72bda4ba0d Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 29 May 2012 20:47:07 +0100
|
||||
Subject: [PATCH 06/13] Add support for ppc64.
|
||||
Subject: [PATCH 06/15] Add support for ppc64.
|
||||
|
||||
Note (1): This patch was rejected upstream because they don't have
|
||||
appropriate hardware for testing.
|
||||
|
205
0007-ppc64-Update-for-OCaml-4.02.0.patch
Normal file
205
0007-ppc64-Update-for-OCaml-4.02.0.patch
Normal file
@ -0,0 +1,205 @@
|
||||
From e07a92272d84fc98ddbe0b42439fa1518283296d Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Fri, 24 Oct 2014 12:59:23 +0200
|
||||
Subject: [PATCH 07/15] ppc64: Update for OCaml 4.02.0.
|
||||
|
||||
These are based on the power (ppc32) branch and some guesswork.
|
||||
In particular, I'm not convinced that my changes to floating
|
||||
point constant handling are correct, although I wrote a small
|
||||
test program which worked.
|
||||
|
||||
Therefore these are not yet integrated into the main patch.
|
||||
---
|
||||
asmcomp/power64/CSE.ml | 37 +++++++++++++++++++++++++++++++++++++
|
||||
asmcomp/power64/emit.mlp | 23 ++++++++++++++---------
|
||||
asmcomp/power64/proc.ml | 8 ++++----
|
||||
asmcomp/power64/scheduling.ml | 2 +-
|
||||
4 files changed, 56 insertions(+), 14 deletions(-)
|
||||
create mode 100644 asmcomp/power64/CSE.ml
|
||||
|
||||
diff --git a/asmcomp/power64/CSE.ml b/asmcomp/power64/CSE.ml
|
||||
new file mode 100644
|
||||
index 0000000..ec10d2d
|
||||
--- /dev/null
|
||||
+++ b/asmcomp/power64/CSE.ml
|
||||
@@ -0,0 +1,37 @@
|
||||
+(***********************************************************************)
|
||||
+(* *)
|
||||
+(* OCaml *)
|
||||
+(* *)
|
||||
+(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
|
||||
+(* *)
|
||||
+(* Copyright 2014 Institut National de Recherche en Informatique et *)
|
||||
+(* en Automatique. All rights reserved. This file is distributed *)
|
||||
+(* under the terms of the Q Public License version 1.0. *)
|
||||
+(* *)
|
||||
+(***********************************************************************)
|
||||
+
|
||||
+(* CSE for the PowerPC *)
|
||||
+
|
||||
+open Arch
|
||||
+open Mach
|
||||
+open CSEgen
|
||||
+
|
||||
+class cse = object (self)
|
||||
+
|
||||
+inherit cse_generic as super
|
||||
+
|
||||
+method! class_of_operation op =
|
||||
+ match op with
|
||||
+ | Ispecific(Imultaddf | Imultsubf) -> Op_pure
|
||||
+ | Ispecific(Ialloc_far _) -> Op_other
|
||||
+ | _ -> super#class_of_operation op
|
||||
+
|
||||
+method! is_cheap_operation op =
|
||||
+ match op with
|
||||
+ | Iconst_int n | Iconst_blockheader n -> n <= 32767n && n >= -32768n
|
||||
+ | _ -> false
|
||||
+
|
||||
+end
|
||||
+
|
||||
+let fundecl f =
|
||||
+ (new cse)#fundecl f
|
||||
diff --git a/asmcomp/power64/emit.mlp b/asmcomp/power64/emit.mlp
|
||||
index d84ac5c..9fd59b2 100644
|
||||
--- a/asmcomp/power64/emit.mlp
|
||||
+++ b/asmcomp/power64/emit.mlp
|
||||
@@ -292,6 +292,7 @@ let name_for_int_comparison = function
|
||||
let name_for_intop = function
|
||||
Iadd -> "add"
|
||||
| Imul -> "mulld"
|
||||
+ | Imulh -> "mulhd"
|
||||
| Idiv -> "divd"
|
||||
| Iand -> "and"
|
||||
| Ior -> "or"
|
||||
@@ -354,7 +355,8 @@ let load_store_size = function
|
||||
let instr_size = function
|
||||
Lend -> 0
|
||||
| Lop(Imove | Ispill | Ireload) -> 1
|
||||
- | Lop(Iconst_int n) -> if is_native_immediate n then 1 else 2
|
||||
+ | Lop(Iconst_int n | Iconst_blockheader n) ->
|
||||
+ if is_native_immediate n then 1 else 2
|
||||
| Lop(Iconst_float s) -> 2
|
||||
| Lop(Iconst_symbol s) -> 2
|
||||
| Lop(Icall_ind) -> 6
|
||||
@@ -370,7 +372,7 @@ let instr_size = function
|
||||
if chunk = Byte_signed
|
||||
then load_store_size addr + 1
|
||||
else load_store_size addr
|
||||
- | Lop(Istore(chunk, addr)) -> load_store_size addr
|
||||
+ | Lop(Istore(chunk, addr, _)) -> load_store_size addr
|
||||
| Lop(Ialloc n) -> 4
|
||||
| Lop(Ispecific(Ialloc_far n)) -> 5
|
||||
| Lop(Iintop Imod) -> 3
|
||||
@@ -397,7 +399,7 @@ let instr_size = function
|
||||
| Lsetuptrap lbl -> 1
|
||||
| Lpushtrap -> 7
|
||||
| Lpoptrap -> 1
|
||||
- | Lraise -> 6
|
||||
+ | Lraise _ -> 6
|
||||
|
||||
let label_map code =
|
||||
let map = Hashtbl.create 37 in
|
||||
@@ -492,7 +494,7 @@ let rec emit_instr i dslot =
|
||||
| (_, _) ->
|
||||
fatal_error "Emit: Imove"
|
||||
end
|
||||
- | Lop(Iconst_int n) ->
|
||||
+ | Lop(Iconst_int n | Iconst_blockheader n) ->
|
||||
if is_native_immediate n then
|
||||
` li {emit_reg i.res.(0)}, {emit_nativeint n}\n`
|
||||
else if n >= -0x8000_0000n && n <= 0x7FFF_FFFFn then begin
|
||||
@@ -502,7 +504,8 @@ let rec emit_instr i dslot =
|
||||
end else begin
|
||||
` ld {emit_reg i.res.(0)}, {emit_tocref (TocInt n)}\n`
|
||||
end
|
||||
- | Lop(Iconst_float s) ->
|
||||
+ | Lop(Iconst_float f) ->
|
||||
+ let s = string_of_float f in
|
||||
` lfd {emit_reg i.res.(0)}, {emit_tocref (TocFloat s)}\n`
|
||||
| Lop(Iconst_symbol s) ->
|
||||
` ld {emit_reg i.res.(0)}, {emit_tocref (TocSymOfs (s,0))}\n`
|
||||
@@ -581,7 +584,7 @@ let rec emit_instr i dslot =
|
||||
emit_load_store loadinstr addr i.arg 0 i.res.(0);
|
||||
if chunk = Byte_signed then
|
||||
` extsb {emit_reg i.res.(0)}, {emit_reg i.res.(0)}\n`
|
||||
- | Lop(Istore(chunk, addr)) ->
|
||||
+ | Lop(Istore(chunk, addr, _)) ->
|
||||
let storeinstr =
|
||||
match chunk with
|
||||
Byte_unsigned | Byte_signed -> "stb"
|
||||
@@ -772,7 +775,7 @@ let rec emit_instr i dslot =
|
||||
` mr {emit_gpr 29}, {emit_gpr 11}\n`
|
||||
| Lpoptrap ->
|
||||
` ld {emit_gpr 29}, 0({emit_gpr 29})\n`
|
||||
- | Lraise ->
|
||||
+ | Lraise _ ->
|
||||
` ld {emit_gpr 0}, 8({emit_gpr 29})\n`;
|
||||
` ld {emit_gpr 1}, 16({emit_gpr 29})\n`;
|
||||
` ld {emit_gpr 2}, 24({emit_gpr 29})\n`;
|
||||
@@ -903,9 +906,11 @@ let emit_item = function
|
||||
| Cint n ->
|
||||
` .quad {emit_nativeint n}\n`
|
||||
| Csingle f ->
|
||||
- ` .float 0d{emit_string f}\n`
|
||||
+ let s = string_of_float f in
|
||||
+ ` .float 0d{emit_string s}\n`
|
||||
| Cdouble f ->
|
||||
- ` .double 0d{emit_string f}\n`
|
||||
+ let s = string_of_float f in
|
||||
+ ` .double 0d{emit_string s}\n`
|
||||
| Csymbol_address s ->
|
||||
` .quad {emit_symbol s}\n`
|
||||
| Clabel_address lbl ->
|
||||
diff --git a/asmcomp/power64/proc.ml b/asmcomp/power64/proc.ml
|
||||
index 372303d..a5a35f3 100644
|
||||
--- a/asmcomp/power64/proc.ml
|
||||
+++ b/asmcomp/power64/proc.ml
|
||||
@@ -85,11 +85,11 @@ let rotate_registers = true
|
||||
(* Representation of hard registers by pseudo-registers *)
|
||||
|
||||
let hard_int_reg =
|
||||
- let v = Array.create 23 Reg.dummy in
|
||||
+ let v = Array.make 23 Reg.dummy in
|
||||
for i = 0 to 22 do v.(i) <- Reg.at_location Int (Reg i) done; v
|
||||
|
||||
let hard_float_reg =
|
||||
- let v = Array.create 31 Reg.dummy in
|
||||
+ let v = Array.make 31 Reg.dummy in
|
||||
for i = 0 to 30 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done; v
|
||||
|
||||
let all_phys_regs =
|
||||
@@ -105,7 +105,7 @@ let stack_slot slot ty =
|
||||
|
||||
let calling_conventions
|
||||
first_int last_int first_float last_float make_stack stack_ofs arg =
|
||||
- let loc = Array.create (Array.length arg) Reg.dummy in
|
||||
+ let loc = Array.make (Array.length arg) Reg.dummy in
|
||||
let int = ref first_int in
|
||||
let float = ref first_float in
|
||||
let ofs = ref stack_ofs in
|
||||
@@ -159,7 +159,7 @@ let loc_results res =
|
||||
|
||||
let poweropen_external_conventions first_int last_int
|
||||
first_float last_float arg =
|
||||
- let loc = Array.create (Array.length arg) Reg.dummy in
|
||||
+ let loc = Array.make (Array.length arg) Reg.dummy in
|
||||
let int = ref first_int in
|
||||
let float = ref first_float in
|
||||
let ofs = ref (14 * size_addr) in
|
||||
diff --git a/asmcomp/power64/scheduling.ml b/asmcomp/power64/scheduling.ml
|
||||
index b7bba9b..b582b6a 100644
|
||||
--- a/asmcomp/power64/scheduling.ml
|
||||
+++ b/asmcomp/power64/scheduling.ml
|
||||
@@ -46,7 +46,7 @@ method reload_retaddr_latency = 12
|
||||
method oper_issue_cycles = function
|
||||
Iconst_float _ | Iconst_symbol _ -> 2
|
||||
| Iload(_, Ibased(_, _)) -> 2
|
||||
- | Istore(_, Ibased(_, _)) -> 2
|
||||
+ | Istore(_, Ibased(_, _), _) -> 2
|
||||
| Ialloc _ -> 4
|
||||
| Iintop(Imod) -> 40 (* assuming full stall *)
|
||||
| Iintop(Icomp _) -> 4
|
||||
--
|
||||
2.0.4
|
||||
|
@ -1,7 +1,7 @@
|
||||
From ab7ac2b3c241dfd2db8f9b6818d324997c982708 Mon Sep 17 00:00:00 2001
|
||||
From 371f3ea408ebfc627ab964bb82efc1b5ced1b9b0 Mon Sep 17 00:00:00 2001
|
||||
From: Michel Normand <normand@linux.vnet.ibm.com>
|
||||
Date: Tue, 18 Mar 2014 09:15:47 -0400
|
||||
Subject: [PATCH 07/13] Add support for ppc64le.
|
||||
Subject: [PATCH 08/15] Add support for ppc64le.
|
||||
|
||||
Signed-off-by: Michel Normand <normand@linux.vnet.ibm.com>
|
||||
---
|
204
0009-ppc64le-Update-for-OCaml-4.02.0.patch
Normal file
204
0009-ppc64le-Update-for-OCaml-4.02.0.patch
Normal file
@ -0,0 +1,204 @@
|
||||
From 2d809c0bf3d0f4106ec7ff9c9e4ee3c8204d9516 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Fri, 24 Oct 2014 12:59:23 +0200
|
||||
Subject: [PATCH 09/15] ppc64le: Update for OCaml 4.02.0.
|
||||
|
||||
These are based on the power (ppc32) branch and some guesswork. In
|
||||
particular, I'm not convinced that my changes to floating point
|
||||
constant handling are correct.
|
||||
|
||||
Therefore these are not yet integrated into the main patch.
|
||||
---
|
||||
asmcomp/power64le/CSE.ml | 37 +++++++++++++++++++++++++++++++++++++
|
||||
asmcomp/power64le/emit.mlp | 23 ++++++++++++++---------
|
||||
asmcomp/power64le/proc.ml | 8 ++++----
|
||||
asmcomp/power64le/scheduling.ml | 2 +-
|
||||
4 files changed, 56 insertions(+), 14 deletions(-)
|
||||
create mode 100644 asmcomp/power64le/CSE.ml
|
||||
|
||||
diff --git a/asmcomp/power64le/CSE.ml b/asmcomp/power64le/CSE.ml
|
||||
new file mode 100644
|
||||
index 0000000..ec10d2d
|
||||
--- /dev/null
|
||||
+++ b/asmcomp/power64le/CSE.ml
|
||||
@@ -0,0 +1,37 @@
|
||||
+(***********************************************************************)
|
||||
+(* *)
|
||||
+(* OCaml *)
|
||||
+(* *)
|
||||
+(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
|
||||
+(* *)
|
||||
+(* Copyright 2014 Institut National de Recherche en Informatique et *)
|
||||
+(* en Automatique. All rights reserved. This file is distributed *)
|
||||
+(* under the terms of the Q Public License version 1.0. *)
|
||||
+(* *)
|
||||
+(***********************************************************************)
|
||||
+
|
||||
+(* CSE for the PowerPC *)
|
||||
+
|
||||
+open Arch
|
||||
+open Mach
|
||||
+open CSEgen
|
||||
+
|
||||
+class cse = object (self)
|
||||
+
|
||||
+inherit cse_generic as super
|
||||
+
|
||||
+method! class_of_operation op =
|
||||
+ match op with
|
||||
+ | Ispecific(Imultaddf | Imultsubf) -> Op_pure
|
||||
+ | Ispecific(Ialloc_far _) -> Op_other
|
||||
+ | _ -> super#class_of_operation op
|
||||
+
|
||||
+method! is_cheap_operation op =
|
||||
+ match op with
|
||||
+ | Iconst_int n | Iconst_blockheader n -> n <= 32767n && n >= -32768n
|
||||
+ | _ -> false
|
||||
+
|
||||
+end
|
||||
+
|
||||
+let fundecl f =
|
||||
+ (new cse)#fundecl f
|
||||
diff --git a/asmcomp/power64le/emit.mlp b/asmcomp/power64le/emit.mlp
|
||||
index 5736a18..3f34102 100644
|
||||
--- a/asmcomp/power64le/emit.mlp
|
||||
+++ b/asmcomp/power64le/emit.mlp
|
||||
@@ -297,6 +297,7 @@ let name_for_int_comparison = function
|
||||
let name_for_intop = function
|
||||
Iadd -> "add"
|
||||
| Imul -> "mulld"
|
||||
+ | Imulh -> "mulhd"
|
||||
| Idiv -> "divd"
|
||||
| Iand -> "and"
|
||||
| Ior -> "or"
|
||||
@@ -359,7 +360,8 @@ let load_store_size = function
|
||||
let instr_size = function
|
||||
Lend -> 0
|
||||
| Lop(Imove | Ispill | Ireload) -> 1
|
||||
- | Lop(Iconst_int n) -> if is_native_immediate n then 1 else 2
|
||||
+ | Lop(Iconst_int n | Iconst_blockheader n) ->
|
||||
+ if is_native_immediate n then 1 else 2
|
||||
| Lop(Iconst_float s) -> 2
|
||||
| Lop(Iconst_symbol s) -> 2
|
||||
| Lop(Icall_ind) -> 4
|
||||
@@ -375,7 +377,7 @@ let instr_size = function
|
||||
if chunk = Byte_signed
|
||||
then load_store_size addr + 1
|
||||
else load_store_size addr
|
||||
- | Lop(Istore(chunk, addr)) -> load_store_size addr
|
||||
+ | Lop(Istore(chunk, addr, _)) -> load_store_size addr
|
||||
| Lop(Ialloc n) -> 4
|
||||
| Lop(Ispecific(Ialloc_far n)) -> 5
|
||||
| Lop(Iintop Imod) -> 3
|
||||
@@ -402,7 +404,7 @@ let instr_size = function
|
||||
| Lsetuptrap lbl -> 1
|
||||
| Lpushtrap -> 7
|
||||
| Lpoptrap -> 1
|
||||
- | Lraise -> 6
|
||||
+ | Lraise _ -> 6
|
||||
|
||||
let label_map code =
|
||||
let map = Hashtbl.create 37 in
|
||||
@@ -497,7 +499,7 @@ let rec emit_instr i dslot =
|
||||
| (_, _) ->
|
||||
fatal_error "Emit: Imove"
|
||||
end
|
||||
- | Lop(Iconst_int n) ->
|
||||
+ | Lop(Iconst_int n | Iconst_blockheader n) ->
|
||||
if is_native_immediate n then
|
||||
` li {emit_reg i.res.(0)}, {emit_nativeint n}\n`
|
||||
else if n >= -0x8000_0000n && n <= 0x7FFF_FFFFn then begin
|
||||
@@ -507,7 +509,8 @@ let rec emit_instr i dslot =
|
||||
end else begin
|
||||
` ld {emit_reg i.res.(0)}, {emit_tocref (TocInt n)}\n`
|
||||
end
|
||||
- | Lop(Iconst_float s) ->
|
||||
+ | Lop(Iconst_float f) ->
|
||||
+ let s = string_of_float f in
|
||||
` lfd {emit_reg i.res.(0)}, {emit_tocref (TocFloat s)}\n`
|
||||
| Lop(Iconst_symbol s) ->
|
||||
` ld {emit_reg i.res.(0)}, {emit_tocref (TocSymOfs (s,0))}\n`
|
||||
@@ -576,7 +579,7 @@ let rec emit_instr i dslot =
|
||||
emit_load_store loadinstr addr i.arg 0 i.res.(0);
|
||||
if chunk = Byte_signed then
|
||||
` extsb {emit_reg i.res.(0)}, {emit_reg i.res.(0)}\n`
|
||||
- | Lop(Istore(chunk, addr)) ->
|
||||
+ | Lop(Istore(chunk, addr, _)) ->
|
||||
let storeinstr =
|
||||
match chunk with
|
||||
Byte_unsigned | Byte_signed -> "stb"
|
||||
@@ -767,7 +770,7 @@ let rec emit_instr i dslot =
|
||||
` mr {emit_gpr 29}, {emit_gpr 11}\n`
|
||||
| Lpoptrap ->
|
||||
` ld {emit_gpr 29}, 0({emit_gpr 29})\n`
|
||||
- | Lraise ->
|
||||
+ | Lraise _ ->
|
||||
` ld {emit_gpr 0}, 8({emit_gpr 29})\n`;
|
||||
` ld {emit_gpr 1}, 16({emit_gpr 29})\n`;
|
||||
` ld {emit_gpr 2}, 24({emit_gpr 29})\n`;
|
||||
@@ -895,9 +898,11 @@ let emit_item = function
|
||||
| Cint n ->
|
||||
` .quad {emit_nativeint n}\n`
|
||||
| Csingle f ->
|
||||
- ` .float 0d{emit_string f}\n`
|
||||
+ let s = string_of_float f in
|
||||
+ ` .float 0d{emit_string s}\n`
|
||||
| Cdouble f ->
|
||||
- ` .double 0d{emit_string f}\n`
|
||||
+ let s = string_of_float f in
|
||||
+ ` .double 0d{emit_string s}\n`
|
||||
| Csymbol_address s ->
|
||||
` .quad {emit_symbol s}\n`
|
||||
| Clabel_address lbl ->
|
||||
diff --git a/asmcomp/power64le/proc.ml b/asmcomp/power64le/proc.ml
|
||||
index 9b98577..476c984 100644
|
||||
--- a/asmcomp/power64le/proc.ml
|
||||
+++ b/asmcomp/power64le/proc.ml
|
||||
@@ -85,11 +85,11 @@ let rotate_registers = true
|
||||
(* Representation of hard registers by pseudo-registers *)
|
||||
|
||||
let hard_int_reg =
|
||||
- let v = Array.create 23 Reg.dummy in
|
||||
+ let v = Array.make 23 Reg.dummy in
|
||||
for i = 0 to 22 do v.(i) <- Reg.at_location Int (Reg i) done; v
|
||||
|
||||
let hard_float_reg =
|
||||
- let v = Array.create 31 Reg.dummy in
|
||||
+ let v = Array.make 31 Reg.dummy in
|
||||
for i = 0 to 30 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done; v
|
||||
|
||||
let all_phys_regs =
|
||||
@@ -105,7 +105,7 @@ let stack_slot slot ty =
|
||||
|
||||
let calling_conventions
|
||||
first_int last_int first_float last_float make_stack stack_ofs arg =
|
||||
- let loc = Array.create (Array.length arg) Reg.dummy in
|
||||
+ let loc = Array.make (Array.length arg) Reg.dummy in
|
||||
let int = ref first_int in
|
||||
let float = ref first_float in
|
||||
let ofs = ref stack_ofs in
|
||||
@@ -159,7 +159,7 @@ let loc_results res =
|
||||
|
||||
let poweropen_external_conventions first_int last_int
|
||||
first_float last_float arg =
|
||||
- let loc = Array.create (Array.length arg) Reg.dummy in
|
||||
+ let loc = Array.make (Array.length arg) Reg.dummy in
|
||||
let int = ref first_int in
|
||||
let float = ref first_float in
|
||||
let ofs = ref (14 * size_addr) in
|
||||
diff --git a/asmcomp/power64le/scheduling.ml b/asmcomp/power64le/scheduling.ml
|
||||
index b7bba9b..b582b6a 100644
|
||||
--- a/asmcomp/power64le/scheduling.ml
|
||||
+++ b/asmcomp/power64le/scheduling.ml
|
||||
@@ -46,7 +46,7 @@ method reload_retaddr_latency = 12
|
||||
method oper_issue_cycles = function
|
||||
Iconst_float _ | Iconst_symbol _ -> 2
|
||||
| Iload(_, Ibased(_, _)) -> 2
|
||||
- | Istore(_, Ibased(_, _)) -> 2
|
||||
+ | Istore(_, Ibased(_, _), _) -> 2
|
||||
| Ialloc _ -> 4
|
||||
| Iintop(Imod) -> 40 (* assuming full stall *)
|
||||
| Iintop(Icomp _) -> 4
|
||||
--
|
||||
2.0.4
|
||||
|
@ -1,7 +1,7 @@
|
||||
From 515d0ac7418f3ec999dae4821ffb4888ef8c9825 Mon Sep 17 00:00:00 2001
|
||||
From 00721516cd921f71f727915e14b723412afe835a Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Sat, 10 May 2014 03:20:35 -0400
|
||||
Subject: [PATCH 08/13] arm, arm64: Mark stack as non-executable.
|
||||
Subject: [PATCH 10/15] arm, arm64: Mark stack as non-executable.
|
||||
|
||||
The same fix as this one, which was only fully applied to
|
||||
i686 & x86-64:
|
@ -1,7 +1,7 @@
|
||||
From c2783885f93b0394376cc99354f67b3647cfcfc2 Mon Sep 17 00:00:00 2001
|
||||
From 8c54b8588ea3000c5082a0a2b2e57c3d5a1a8655 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 1 Apr 2014 11:17:07 +0100
|
||||
Subject: [PATCH 09/13] arg: Add no_arg and get_arg helper functions.
|
||||
Subject: [PATCH 11/15] arg: Add no_arg and get_arg helper functions.
|
||||
|
||||
The no_arg function in this patch is a no-op. It will do something
|
||||
useful in the followups.
|
@ -1,7 +1,7 @@
|
||||
From 21a743dc1983b3b41ddaa790c621fe0b46969e1f Mon Sep 17 00:00:00 2001
|
||||
From 857b0cdc2ac37926e625034e5e62114e103cfe9e Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Tue, 1 Apr 2014 11:21:40 +0100
|
||||
Subject: [PATCH 10/13] arg: Allow flags such as --flag=arg as well as --flag
|
||||
Subject: [PATCH 12/15] arg: Allow flags such as --flag=arg as well as --flag
|
||||
arg.
|
||||
|
||||
Allow flags to be followed directly by their argument, separated by an '='
|
@ -1,7 +1,7 @@
|
||||
From 8dcd718671ad2bd5384a9d9ffeed7d33b1b34a27 Mon Sep 17 00:00:00 2001
|
||||
From d58a221d0fd307d80bed6cfcec67a1c97e47439c Mon Sep 17 00:00:00 2001
|
||||
From: Xavier Leroy <xavier.leroy@inria.fr>
|
||||
Date: Wed, 27 Aug 2014 09:58:33 +0000
|
||||
Subject: [PATCH 11/13] PR#6517: use ISO C99 types {,u}int{32,64}_t in
|
||||
Subject: [PATCH 13/15] PR#6517: use ISO C99 types {,u}int{32,64}_t in
|
||||
preference to our homegrown types {,u}int{32,64}.
|
||||
|
||||
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15131 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
|
@ -1,7 +1,7 @@
|
||||
From 719dd72c791d557ab6bc17a1327a36fb04ea9237 Mon Sep 17 00:00:00 2001
|
||||
From 907e64f45ad87b746aad704af717b067d0909014 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Thu, 11 Sep 2014 14:49:54 +0100
|
||||
Subject: [PATCH 12/13] ppc, ppc64, ppc64le: Mark stack as non-executable.
|
||||
Subject: [PATCH 14/15] ppc, ppc64, ppc64le: Mark stack as non-executable.
|
||||
|
||||
The same fix as this one, which was only fully applied to
|
||||
i686 & x86-64:
|
@ -1,7 +1,7 @@
|
||||
From 0d60237e349595e1022c2258fe6fcb4137d9e128 Mon Sep 17 00:00:00 2001
|
||||
From a3cbc5d7e8f5576c9b0d5fb32b359d75c0edfdb1 Mon Sep 17 00:00:00 2001
|
||||
From: "Richard W.M. Jones" <rjones@redhat.com>
|
||||
Date: Fri, 24 Oct 2014 10:10:54 +0100
|
||||
Subject: [PATCH 13/13] ppc64/ppc64le: proc: Interim definitions for op_is_pure
|
||||
Subject: [PATCH 15/15] ppc64/ppc64le: proc: Interim definitions for op_is_pure
|
||||
and regs_are_volatile.
|
||||
|
||||
See: https://bugzilla.redhat.com/show_bug.cgi?id=1156300
|
||||
@ -14,7 +14,7 @@ someone more familiar with the compiler and POWER architecture.
|
||||
2 files changed, 30 insertions(+)
|
||||
|
||||
diff --git a/asmcomp/power64/proc.ml b/asmcomp/power64/proc.ml
|
||||
index 372303d..85a8742 100644
|
||||
index a5a35f3..c377f69 100644
|
||||
--- a/asmcomp/power64/proc.ml
|
||||
+++ b/asmcomp/power64/proc.ml
|
||||
@@ -202,6 +202,10 @@ let loc_external_results res =
|
||||
@ -47,7 +47,7 @@ index 372303d..85a8742 100644
|
||||
|
||||
let num_stack_slots = [| 0; 0 |]
|
||||
diff --git a/asmcomp/power64le/proc.ml b/asmcomp/power64le/proc.ml
|
||||
index 9b98577..ea956b8 100644
|
||||
index 476c984..56473ac 100644
|
||||
--- a/asmcomp/power64le/proc.ml
|
||||
+++ b/asmcomp/power64le/proc.ml
|
||||
@@ -202,6 +202,10 @@ let loc_external_results res =
|
20
ocaml.spec
20
ocaml.spec
@ -17,7 +17,7 @@
|
||||
|
||||
Name: ocaml
|
||||
Version: 4.02.0
|
||||
Release: 5%{?dist}
|
||||
Release: 6%{?dist}
|
||||
|
||||
Summary: OCaml compiler and programming environment
|
||||
|
||||
@ -51,13 +51,15 @@ Patch0003: 0003-Don-t-add-rpaths-to-libraries.patch
|
||||
Patch0004: 0004-ocamlbyteinfo-ocamlplugininfo-Useful-utilities-from-.patch
|
||||
Patch0005: 0005-configure-Allow-user-defined-C-compiler-flags.patch
|
||||
Patch0006: 0006-Add-support-for-ppc64.patch
|
||||
Patch0007: 0007-Add-support-for-ppc64le.patch
|
||||
Patch0008: 0008-arm-arm64-Mark-stack-as-non-executable.patch
|
||||
Patch0009: 0009-arg-Add-no_arg-and-get_arg-helper-functions.patch
|
||||
Patch0010: 0010-arg-Allow-flags-such-as-flag-arg-as-well-as-flag-arg.patch
|
||||
Patch0011: 0011-PR-6517-use-ISO-C99-types-u-int-32-64-_t-in-preferen.patch
|
||||
Patch0012: 0012-ppc-ppc64-ppc64le-Mark-stack-as-non-executable.patch
|
||||
Patch0013: 0013-ppc64-ppc64le-proc-Interim-definitions-for-op_is_pur.patch
|
||||
Patch0007: 0007-ppc64-Update-for-OCaml-4.02.0.patch
|
||||
Patch0008: 0008-Add-support-for-ppc64le.patch
|
||||
Patch0009: 0009-ppc64le-Update-for-OCaml-4.02.0.patch
|
||||
Patch0010: 0010-arm-arm64-Mark-stack-as-non-executable.patch
|
||||
Patch0011: 0011-arg-Add-no_arg-and-get_arg-helper-functions.patch
|
||||
Patch0012: 0012-arg-Allow-flags-such-as-flag-arg-as-well-as-flag-arg.patch
|
||||
Patch0013: 0013-PR-6517-use-ISO-C99-types-u-int-32-64-_t-in-preferen.patch
|
||||
Patch0014: 0014-ppc-ppc64-ppc64le-Mark-stack-as-non-executable.patch
|
||||
Patch0015: 0015-ppc64-ppc64le-proc-Interim-definitions-for-op_is_pur.patch
|
||||
|
||||
# Add BFD support so that ocamlobjinfo supports *.cmxs format (RHBZ#1113735).
|
||||
BuildRequires: binutils-devel
|
||||
@ -420,7 +422,7 @@ fi
|
||||
|
||||
|
||||
%changelog
|
||||
* Fri Oct 24 2014 Richard W.M. Jones <rjones@redhat.com> - 4.02.0-5
|
||||
* Fri Oct 24 2014 Richard W.M. Jones <rjones@redhat.com> - 4.02.0-6
|
||||
- Fixes for ppc64/ppc64le (RHBZ#1156300).
|
||||
|
||||
* Mon Oct 20 2014 Richard W.M. Jones <rjones@redhat.com> - 4.02.0-4
|
||||
|
Loading…
Reference in New Issue
Block a user