summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--asmcomp/emit_alpha.mlp5
-rw-r--r--asmcomp/emit_i386.mlp21
-rw-r--r--asmcomp/emit_sparc.mlp2
-rw-r--r--asmcomp/proc_i386.ml8
4 files changed, 23 insertions, 13 deletions
diff --git a/asmcomp/emit_alpha.mlp b/asmcomp/emit_alpha.mlp
index 2268686a3..fc135fd37 100644
--- a/asmcomp/emit_alpha.mlp
+++ b/asmcomp/emit_alpha.mlp
@@ -515,9 +515,8 @@ let emit_instr i =
begin match Array.length jumptbl with
3 ->
(* Should eliminate the branches that just fall through *)
- ` subq {emit_reg i.arg.(0)}, 1, $25\n`;
- ` blt $25, {emit_label jumptbl.(0)}\n`;
- ` beq $25, {emit_label jumptbl.(1)}\n`;
+ ` beq {emit_reg i.arg.(0)}, {emit_label jumptbl.(0)}\n`;
+ ` blbs {emit_reg i.arg.(0)}, {emit_label jumptbl.(1)}\n`;
` br {emit_label jumptbl.(2)}\n`
| 4 ->
` beq {emit_reg i.arg.(0)}, {emit_label jumptbl.(0)}\n`;
diff --git a/asmcomp/emit_i386.mlp b/asmcomp/emit_i386.mlp
index ab486a2ab..6e1001ee3 100644
--- a/asmcomp/emit_i386.mlp
+++ b/asmcomp/emit_i386.mlp
@@ -144,6 +144,13 @@ let name_for_cond_branch = function
| Iunsigned Cle -> "be" | Iunsigned Cgt -> "a"
| Iunsigned Clt -> "b" | Iunsigned Cge -> "ae"
+(* Output a comparison with a constant *)
+
+let output_comparison arg n =
+ match arg.loc with
+ Reg r when n = 0 -> ` testl {emit_reg arg}, {emit_reg arg}\n`
+ | _ -> ` cmpl ${emit_int n}, {emit_reg arg}\n`
+
(* Output the assembly code for an instruction *)
(* Name of current function *)
@@ -216,7 +223,9 @@ let emit_instr i =
record_frame i.live
end else begin
` call {emit_symbol s}\n`
- end
+ end;
+ if Array.length i.res > 0 & i.res.(0).typ = Float then
+ ` fstpl {emit_shift i.res.(0)}\n`
| Lop(Istackoffset n) ->
if n >= 0
then ` subl ${emit_int n}, %esp\n`
@@ -266,8 +275,8 @@ let emit_instr i =
` cmpl _young_start, %eax\n`;
let lbl_cont = record_frame_label i.live in
` jae {emit_label lbl_cont}\n`;
- ` movl ${emit_int n}, %eax\n`;
` call _caml_call_gc\n`;
+ ` .word {emit_int n}\n`;
`{emit_label lbl_cont}: leal 4(%eax), {emit_reg i.res.(0)}\n`
end else begin
begin match n with
@@ -285,7 +294,7 @@ let emit_instr i =
` set{emit_string b} %al\n`;
` movzbl %al, {emit_reg i.res.(0)}\n`
| Lop(Iintop_imm(Icomp cmp, n)) ->
- ` cmpl ${emit_int n}, {emit_reg i.arg.(0)}\n`;
+ output_comparison i.arg.(0) n;
let b = name_for_cond_branch cmp in
` set{emit_string b} %al\n`;
` movzbl %al, {emit_reg i.res.(0)}\n`
@@ -380,17 +389,17 @@ let emit_instr i =
| Lcondbranch(tst, lbl) ->
begin match tst with
Itruetest ->
- ` cmpl $0, {emit_reg i.arg.(0)}\n`;
+ output_comparison i.arg.(0) 0;
` jne {emit_label lbl}\n`
| Ifalsetest ->
- ` cmpl $0, {emit_reg i.arg.(0)}\n`;
+ output_comparison i.arg.(0) 0;
` je {emit_label lbl}\n`
| Iinttest cmp ->
` cmpl {emit_reg i.arg.(1)}, {emit_reg i.arg.(0)}\n`;
let b = name_for_cond_branch cmp in
` j{emit_string b} {emit_label lbl}\n`
| Iinttest_imm(cmp, n) ->
- ` cmpl ${emit_int n}, {emit_reg i.arg.(0)}\n`;
+ output_comparison i.arg.(0) n;
let b = name_for_cond_branch cmp in
` j{emit_string b} {emit_label lbl}\n`
| Ifloattest cmp ->
diff --git a/asmcomp/emit_sparc.mlp b/asmcomp/emit_sparc.mlp
index ba60ca2b6..be804cd74 100644
--- a/asmcomp/emit_sparc.mlp
+++ b/asmcomp/emit_sparc.mlp
@@ -225,7 +225,7 @@ let emit_instr i =
` ldd [%sp + 96], {emit_reg dst}\n`
else begin
` ld [%sp + 96], {emit_reg dst}\n`;
- ` ld [%sp + 96], {emit_reg(next_in_pair dst)}\n`
+ ` ld [%sp + 100], {emit_reg(next_in_pair dst)}\n`
end;
` add %sp, 8, %sp\n`
| {loc = Reg rs; typ = (Int | Addr)}, {loc = Stack sd} ->
diff --git a/asmcomp/proc_i386.ml b/asmcomp/proc_i386.ml
index 9ee1a97bc..0dc23ea29 100644
--- a/asmcomp/proc_i386.ml
+++ b/asmcomp/proc_i386.ml
@@ -189,11 +189,13 @@ let pseudoregs_for_operation op arg res =
(* For shifts with variable shift count, second arg must be in ecx *)
| Iintop(Ilsl|Ilsr|Iasr) ->
([|res.(0); phys_reg 2|], res)
- (* For div and mod, first arg must be in eax, result is in eax or edx *)
+ (* For div and mod, first arg must be in eax, edx is clobbered,
+ and result is in eax or edx respectively.
+ Keep it simple, just force second argument in ecx. *)
| Iintop(Idiv) ->
- ([|phys_reg 0; arg.(1)|], [|phys_reg 0|])
+ ([|phys_reg 0; phys_reg 2|], [|phys_reg 0|])
| Iintop(Imod) ->
- ([|phys_reg 0; arg.(1)|], [|phys_reg 3|])
+ ([|phys_reg 0; phys_reg 2|], [|phys_reg 3|])
(* For storing a byte, the argument must be in eax...edx.
For storing a halfword, any reg is ok.
Keep it simple, just force it to be in edx in both cases. *)