summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--asmcomp/asmlink.ml5
-rw-r--r--asmcomp/cmmgen.ml5
-rw-r--r--asmcomp/cmmgen.mli1
-rw-r--r--asmcomp/emit_alpha.mlp13
-rw-r--r--asmcomp/emit_mips.mlp12
5 files changed, 27 insertions, 9 deletions
diff --git a/asmcomp/asmlink.ml b/asmcomp/asmlink.ml
index 897096f19..f0d578756 100644
--- a/asmcomp/asmlink.ml
+++ b/asmcomp/asmlink.ml
@@ -131,6 +131,9 @@ let make_startup_file filename info_list =
IntSet.iter
(fun n -> List.iter Asmgen.compile_phrase (Cmmgen.curry_function n))
!curry_functions;
+ Array.iter
+ (fun name -> Asmgen.compile_phrase(Cmmgen.predef_exception name))
+ Runtimedef.builtin_exceptions;
Asmgen.compile_phrase(Cmmgen.global_table name_list);
Asmgen.compile_phrase(Cmmgen.frame_table ("startup" :: name_list));
Emit.end_assembly();
@@ -145,7 +148,7 @@ let call_linker file_list startup_file =
if Sys.command
(Printf.sprintf
"%s -I%s -o %s %s %s %s -L%s %s %s %s"
- Config.c_compiler
+ Config.native_c_compiler
Config.standard_library
!Clflags.exec_name
(String.concat " " (List.rev !Clflags.ccopts))
diff --git a/asmcomp/cmmgen.ml b/asmcomp/cmmgen.ml
index 446e9864f..bba5764df 100644
--- a/asmcomp/cmmgen.ml
+++ b/asmcomp/cmmgen.ml
@@ -814,3 +814,8 @@ let frame_table namelist =
Cdata(Cdefine_symbol "caml_frametable" ::
List.map (fun name -> Csymbol_address(name ^ "_frametable")) namelist @
[Cint 0])
+
+(* Initialize a predefined exception *)
+
+let predef_exception name =
+ Cdata(emit_constant name (Const_block(0,[Const_base(Const_string name)])) [])
diff --git a/asmcomp/cmmgen.mli b/asmcomp/cmmgen.mli
index a0722ccbe..69e858ed3 100644
--- a/asmcomp/cmmgen.mli
+++ b/asmcomp/cmmgen.mli
@@ -7,3 +7,4 @@ val curry_function: int -> Cmm.phrase list
val entry_point: string list -> Cmm.phrase
val global_table: string list -> Cmm.phrase
val frame_table: string list -> Cmm.phrase
+val predef_exception: string -> Cmm.phrase
diff --git a/asmcomp/emit_alpha.mlp b/asmcomp/emit_alpha.mlp
index 5eb1f4be3..fd8919739 100644
--- a/asmcomp/emit_alpha.mlp
+++ b/asmcomp/emit_alpha.mlp
@@ -94,6 +94,7 @@ let liveregs instr extra_msk =
let live_24 = 1 lsl (31 - 24)
let live_25 = 1 lsl (31 - 25)
+let live_26 = 1 lsl (31 - 26)
let live_27 = 1 lsl (31 - 27)
(* Record live pointers at call points *)
@@ -311,26 +312,30 @@ let emit_instr i =
`{record_frame i.live} bsr {emit_symbol s}\n`
| Lop(Itailcall_ind) ->
let n = frame_size() in
- if !contains_calls then
+ if !contains_calls then begin
` ldq $26, {emit_int(n - 8)}($sp)\n`;
+ ` andnot $26, 1, $26\n`
+ end;
if !uses_gp then
` ldq $gp, {emit_int(n - 16)}($sp)\n`;
if n > 0 then
` lda $sp, {emit_int n}($sp)\n`;
- liveregs i 0;
+ liveregs i live_26;
` jmp ({emit_reg i.arg.(0)})\n`
| Lop(Itailcall_imm s) ->
if s = !function_name then begin
` br {emit_label !tailrec_entry_point}\n`
end else begin
let n = frame_size() in
- if !contains_calls then
+ if !contains_calls then begin
` ldq $26, {emit_int(n - 8)}($sp)\n`;
+ ` andnot $26, 1, $26\n`
+ end;
if !uses_gp then
` ldq $gp, {emit_int(n - 16)}($sp)\n`;
if n > 0 then
` lda $sp, {emit_int n}($sp)\n`;
- liveregs i 0;
+ liveregs i live_26;
` br {emit_symbol s}\n`
end
| Lop(Iextcall(s, alloc)) ->
diff --git a/asmcomp/emit_mips.mlp b/asmcomp/emit_mips.mlp
index 4d1bd7bc4..199228098 100644
--- a/asmcomp/emit_mips.mlp
+++ b/asmcomp/emit_mips.mlp
@@ -218,8 +218,10 @@ let emit_instr i =
`{record_frame i.live} jal {emit_symbol s}\n`
| Lop(Itailcall_ind) ->
let n = frame_size() in
- if !contains_calls then
+ if !contains_calls then begin
` lw $31, {emit_int(n - 4)}($sp)\n`;
+ ` and $31, $31, -2\n`
+ end;
if n > 0 then
` addu $sp, $sp, {emit_int n}\n`;
liveregs i 0;
@@ -229,8 +231,10 @@ let emit_instr i =
` b {emit_label !tailrec_entry_point}\n`
end else begin
let n = frame_size() in
- if !contains_calls then
+ if !contains_calls then begin
` lw $31, {emit_int(n - 4)}($sp)\n`;
+ ` and $31, $31, -2\n`
+ end;
if n > 0 then
` addu $sp, $sp, {emit_int n}\n`;
liveregs i 0;
@@ -347,10 +351,10 @@ let emit_instr i =
` bc1{emit_string test} {emit_label lbl}\n`
| Ioddtest ->
` and $25, {emit_reg i.arg.(0)}, 1\n`;
- ` bne $25, 0, {emit_label lbl}\n`
+ ` bne $25, $0, {emit_label lbl}\n`
| Ieventest ->
` and $25, {emit_reg i.arg.(0)}, 1\n`;
- ` beq $25, 0, {emit_label lbl}\n`
+ ` beq $25, $0, {emit_label lbl}\n`
end
| Lswitch jumptbl ->
(* Switches with 1 or 2 cases have normally been eliminated before *)