summaryrefslogtreecommitdiffstats
path: root/asmcomp/sparc
diff options
context:
space:
mode:
Diffstat (limited to 'asmcomp/sparc')
-rw-r--r--asmcomp/sparc/emit.mlp32
-rw-r--r--asmcomp/sparc/scheduling.ml2
-rw-r--r--asmcomp/sparc/selection.ml14
3 files changed, 9 insertions, 39 deletions
diff --git a/asmcomp/sparc/emit.mlp b/asmcomp/sparc/emit.mlp
index 6c7e86da8..1d0699fb4 100644
--- a/asmcomp/sparc/emit.mlp
+++ b/asmcomp/sparc/emit.mlp
@@ -443,36 +443,15 @@ let rec emit_instr i dslot =
` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
` wr %g1, %y\n`;
` sdiv {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.res.(0)}\n`
+ | Lop(Iintop Imulh) ->
+ ` smul {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, %g1\n`;
+ ` rd %y, {emit_reg i.res.(0)}\n`
| Lop(Iintop op) ->
let instr = name_for_int_operation op in
` {emit_string instr} {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.res.(0)}\n`
| Lop(Iintop_imm(Ilsl, 1)) ->
(* UltraSPARC has two add units but only one shifter. *)
` add {emit_reg i.arg.(0)}, {emit_reg i.arg.(0)}, {emit_reg i.res.(0)}\n`
- | Lop(Iintop_imm(Idiv, n)) ->
- let l = Misc.log2 n in
- if n = 1 lsl l then begin
- let lbl = new_label() in
- ` cmp {emit_reg i.arg.(0)}, 0\n`;
- ` bge {emit_label lbl}\n`;
- ` mov {emit_reg i.arg.(0)}, %g1\n`; (* in delay slot *)
- ` add %g1, {emit_int (n-1)}, %g1\n`;
- `{emit_label lbl}:\n`;
- ` sra %g1, {emit_int l}, {emit_reg i.res.(0)}\n`
- end else begin
- ` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
- ` wr %g1, %y\n`;
- ` sdiv {emit_reg i.arg.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`
- end
- | Lop(Iintop_imm(Imod, n)) -> (* n is a power of 2 *)
- let lbl = new_label() in
- ` tst {emit_reg i.arg.(0)}\n`;
- ` bge {emit_label lbl}\n`;
- ` andcc {emit_reg i.arg.(0)}, {emit_int (n-1)}, {emit_reg i.res.(0)}\n`; (* in delay slot *)
- ` be {emit_label lbl}\n`;
- ` nop\n`;
- ` sub {emit_reg i.res.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`;
- `{emit_label lbl}:\n`
| Lop(Iintop_imm(Icomp cmp, n)) ->
` cmp {emit_reg i.arg.(0)}, {emit_int n}\n`;
if !arch_version = SPARC_V9 then begin
@@ -496,6 +475,9 @@ let rec emit_instr i dslot =
` bleu {emit_label !range_check_trap}\n`;
` nop\n` (* delay slot *)
end
+ | Lop(Iintop_imm(Imulh, n)) ->
+ ` smul {emit_reg i.arg.(0)}, {emit_int n}, %g1\n`;
+ ` rd %y, {emit_reg i.res.(0)}\n`
| Lop(Iintop_imm(op, n)) ->
let instr = name_for_int_operation op in
` {emit_string instr} {emit_reg i.arg.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`
@@ -618,7 +600,7 @@ and fill_delay_slot = function
that does not branch. *)
let is_one_instr_op = function
- Idiv | Imod | Icomp _ | Icheckbound -> false
+ Imulh | Idiv | Imod | Icomp _ | Icheckbound -> false
| _ -> true
let is_one_instr i =
diff --git a/asmcomp/sparc/scheduling.ml b/asmcomp/sparc/scheduling.ml
index 048880abd..497722bbc 100644
--- a/asmcomp/sparc/scheduling.ml
+++ b/asmcomp/sparc/scheduling.ml
@@ -47,8 +47,6 @@ method oper_issue_cycles = function
| Ialloc _ -> 6
| Iintop(Icomp _) -> 4
| Iintop(Icheckbound) -> 2
- | Iintop_imm(Idiv, _) -> 5
- | Iintop_imm(Imod, _) -> 5
| Iintop_imm(Icomp _, _) -> 4
| Iintop_imm(Icheckbound, _) -> 2
| Inegf -> 2
diff --git a/asmcomp/sparc/selection.ml b/asmcomp/sparc/selection.ml
index 055b78f19..d938c1eff 100644
--- a/asmcomp/sparc/selection.ml
+++ b/asmcomp/sparc/selection.ml
@@ -38,23 +38,13 @@ method select_addressing chunk = function
method! select_operation op args =
match (op, args) with
(* For SPARC V7 multiplication, division and modulus are turned into
- calls to C library routines, except if the dividend is a power of 2.
+ calls to C library routines.
For SPARC V8 and V9, use hardware multiplication and division,
but C library routine for modulus. *)
- (Cmuli, [arg; Cconst_int n]) when n = 1 lsl (Misc.log2 n) ->
- (Iintop_imm(Ilsl, Misc.log2 n), [arg])
- | (Cmuli, [Cconst_int n; arg]) when n = 1 lsl (Misc.log2 n) ->
- (Iintop_imm(Ilsl, Misc.log2 n), [arg])
- | (Cmuli, _) when !arch_version = SPARC_V7 ->
+ (Cmuli, _) when !arch_version = SPARC_V7 ->
(Iextcall(".umul", false), args)
- | (Cdivi, [arg; Cconst_int n])
- when self#is_immediate n && n = 1 lsl (Misc.log2 n) ->
- (Iintop_imm(Idiv, n), [arg])
| (Cdivi, _) when !arch_version = SPARC_V7 ->
(Iextcall(".div", false), args)
- | (Cmodi, [arg; Cconst_int n])
- when self#is_immediate n && n = 1 lsl (Misc.log2 n) ->
- (Iintop_imm(Imod, n), [arg])
| (Cmodi, _) ->
(Iextcall(".rem", false), args)
| _ ->