Fix ppc64 TOC load for exception handler addresses (#8506)

The address was loaded from the TOC into register r0.  This generated  bad code in the "big TOC" case, as r0 was used as index register.  The fix is to use another temporary register instead of r0.
Add "arch_power" builtin to ocamltest.
Add test case.
master
Mark Shinwell 2019-03-18 12:31:57 +00:00 committed by Xavier Leroy
parent db1e59d727
commit 0933593596
6 changed files with 36 additions and 3 deletions

View File

@ -198,8 +198,11 @@ let emit_toctable () =
`{emit_label lbl}: .quad {emit_tocentry entry}\n`)
tocref_entries
(* Emit a load from a TOC entry *)
(* Emit a load from a TOC entry.
The [dest] should not be r0, since [dest] is used as the index register for a
ld instruction, but r0 reads as zero when used as an index register.
*)
let emit_tocload emit_dest dest entry =
let lbl = label_for_tocref entry in
if !big_toc || !Clflags.for_package <> None then begin
@ -969,9 +972,9 @@ let emit_instr i =
| ELF64v1 | ELF64v2 ->
` addi 1, 1, {emit_int (-trap_size)}\n`;
adjust_stack_offset trap_size;
emit_tocload emit_gpr 0 (TocLabel lbl_handler);
` std 0, {emit_int trap_handler_offset}(1)\n`;
` std 29, {emit_int trap_previous_offset}(1)\n`;
emit_tocload emit_gpr 29 (TocLabel lbl_handler);
` std 29, {emit_int trap_handler_offset}(1)\n`;
` mr 29, 1\n`
end
| Lpoptrap ->

View File

@ -145,6 +145,12 @@ let arch64 = make
"64-bit architecture"
"non-64-bit architecture")
let arch_power = make
"arch_power"
(Actions_helpers.pass_or_skip (String.equal Ocamltest_config.arch "power")
"Target is POWER architecture"
"Target is not POWER architecture")
let has_symlink = make
"has_symlink"
(Actions_helpers.pass_or_skip (Sys.has_symlink () )
@ -208,4 +214,5 @@ let _ =
run;
script;
check_program_output;
arch_power;
]

View File

@ -34,6 +34,9 @@ val not_bsd : Actions.t
val arch32 : Actions.t
val arch64 : Actions.t
(** Whether the compiler target is POWER architecture. *)
val arch_power : Actions.t
val has_symlink : Actions.t
val setup_build_env : Actions.t

View File

@ -0,0 +1,19 @@
(* TEST
* arch_power
** native
*** ocamlopt.byte
ocamlopt_flags = "-flarge-toc"
**** run
*)
(* GPR#8506
This isn't guaranteed to fail even without the fix from #8506, because
the @ha relocation on the TOC entry for the exception handler's address
might be zero, in which case the linker optimises the code sequence to one
that will not fail.
*)
let () =
try failwith "foo"
with (Failure _) -> ()

View File

@ -0,0 +1 @@
exn_raise.ml