Ne pas employer les instructions smul et sdiv. Appeler les fns de bibliotheque a la place

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@543 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1995-12-17 13:18:37 +00:00
parent e3fd81b00d
commit 7791871296
2 changed files with 47 additions and 62 deletions

View File

@ -64,7 +64,8 @@ let symbol_prefix =
| _ -> fatal_error "Emit_sparc.symbol_prefix" | _ -> fatal_error "Emit_sparc.symbol_prefix"
let emit_symbol s = let emit_symbol s =
emit_string symbol_prefix; Emitaux.emit_symbol s if not(String.length s >= 1 & s.[0] = '.') then emit_string symbol_prefix;
Emitaux.emit_symbol s
(* Output a label *) (* Output a label *)
@ -204,7 +205,6 @@ let emit_float_constant (lbl, cst) =
let name_for_int_operation = function let name_for_int_operation = function
Iadd -> "add" Iadd -> "add"
| Isub -> "sub" | Isub -> "sub"
| Imul -> "smul"
| Iand -> "and" | Iand -> "and"
| Ior -> "or" | Ior -> "or"
| Ixor -> "xor" | Ixor -> "xor"
@ -370,22 +370,6 @@ let rec emit_instr i dslot =
` mov {emit_int n}, %g4\n`; (* in delay slot *) ` mov {emit_int n}, %g4\n`; (* in delay slot *)
` add %g6, 4, {emit_reg i.res.(0)}\n` ` add %g6, 4, {emit_reg i.res.(0)}\n`
end end
| Lop(Iintop Idiv) ->
` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
` wr %g0, %g1, %y\n`;
` nop\n`;
` nop\n`;
` nop\n`;
` sdiv {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.res.(0)}\n`
| Lop(Iintop Imod) ->
` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
` wr %g0, %g1, %y\n`;
` nop\n`;
` nop\n`;
` nop\n`;
` sdiv {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, %g1\n`;
` smul %g1, {emit_reg i.arg.(1)}, %g1\n`;
` sub {emit_reg i.arg.(0)}, %g1, {emit_reg i.res.(0)}\n`
| Lop(Iintop(Icomp cmp)) -> | Lop(Iintop(Icomp cmp)) ->
let comp = name_for_int_comparison cmp in let comp = name_for_int_comparison cmp in
` cmp {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`; ` cmp {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}\n`;
@ -400,9 +384,8 @@ let rec emit_instr i dslot =
| Lop(Iintop op) -> | Lop(Iintop op) ->
let instr = name_for_int_operation op in 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` ` {emit_string instr} {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.res.(0)}\n`
| Lop(Iintop_imm(Idiv, n)) -> | Lop(Iintop_imm(Idiv, n)) -> (* n is a power of 2 *)
let l = Misc.log2 n in let l = Misc.log2 n in
if n = 1 lsl l then begin
let lbl = new_label() in let lbl = new_label() in
` cmp {emit_reg i.arg.(0)}, 0\n`; ` cmp {emit_reg i.arg.(0)}, 0\n`;
` bge {emit_label lbl}\n`; ` bge {emit_label lbl}\n`;
@ -410,17 +393,7 @@ let rec emit_instr i dslot =
` add %g1, {emit_int (n-1)}, %g1\n`; ` add %g1, {emit_int (n-1)}, %g1\n`;
`{emit_label lbl}:\n`; `{emit_label lbl}:\n`;
` sra %g1, {emit_int l}, {emit_reg i.res.(0)}\n` ` sra %g1, {emit_int l}, {emit_reg i.res.(0)}\n`
end else begin | Lop(Iintop_imm(Imod, n)) -> (* n is a power of 2 *)
` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
` wr %g0, %g1, %y\n`;
` nop\n`;
` nop\n`;
` nop\n`;
` sdiv {emit_reg i.arg.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`
end
| Lop(Iintop_imm(Imod, n)) ->
let l = Misc.log2 n in
if n = 1 lsl l then begin
let lbl = new_label() in let lbl = new_label() in
` tst {emit_reg i.arg.(0)}\n`; ` tst {emit_reg i.arg.(0)}\n`;
` bge {emit_label lbl}\n`; ` bge {emit_label lbl}\n`;
@ -429,16 +402,6 @@ let rec emit_instr i dslot =
` nop\n`; ` nop\n`;
` sub {emit_reg i.res.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`; ` sub {emit_reg i.res.(0)}, {emit_int n}, {emit_reg i.res.(0)}\n`;
`{emit_label lbl}:\n` `{emit_label lbl}:\n`
end else begin
` sra {emit_reg i.arg.(0)}, 31, %g1\n`;
` wr %g0, %g1, %y\n`;
` nop\n`;
` nop\n`;
` nop\n`;
` sdiv {emit_reg i.arg.(0)}, {emit_int n}, %g1\n`;
` smul %g1, {emit_int n}, %g1\n`;
` sub {emit_reg i.arg.(0)}, %g1, {emit_reg i.res.(0)}\n`
end
| Lop(Iintop_imm(Icomp cmp, n)) -> | Lop(Iintop_imm(Icomp cmp, n)) ->
let comp = name_for_int_comparison cmp in let comp = name_for_int_comparison cmp in
` cmp {emit_reg i.arg.(0)}, {emit_int n}\n`; ` cmp {emit_reg i.arg.(0)}, {emit_int n}\n`;

View File

@ -58,7 +58,33 @@ let select_addressing exp =
(* Instruction selection *) (* Instruction selection *)
let select_oper op args = raise Use_default let select_oper op args =
(* Multiplication, division and modulus are turned into
calls to C library routines, except if the dividend is a power of 2. *)
(Cmuli, [arg; Cconst_int n]) ->
let l = Misc.log2 n in
if n = 1 lsl l
then (Iintop_imm(Ilsl, l), [arg])
else (Iextcall(".umul", false), args)
| (Cmuli, [Cconst_int n; arg]) ->
let l = Misc.log2 n in
if n = 1 lsl l
then (Iintop_imm(Ilsl, l), [arg])
else (Iextcall(".umul", false), args)
| (Cmuli, _) ->
(Iextcall(".umul", false), args)
| (Cdivi, [arg; Cconst_int n])
when is_immediate n & n = 1 lsl (Misc.log2 n) ->
(Iintop_imm(Idiv, n), [arg])
| (Cdivi, _) ->
(Iextcall(".div", false), args)
| (Cmodi, [arg; Cconst_int n])
when is_immediate n & n = 1 lsl (Misc.log2 n) ->
(Iintop_imm(Imod, n), [arg])
| (Cmodi, _) ->
(Iextcall(".mod", false), args)
| _ ->
raise Use_default
let select_store addr exp = raise Use_default let select_store addr exp = raise Use_default
@ -183,7 +209,7 @@ let loc_results res =
let (loc, ofs) = calling_conventions 8 13 100 105 not_supported res in loc let (loc, ofs) = calling_conventions 8 13 100 105 not_supported res in loc
(* On the Sparc, all arguments to C functions, even floating-point arguments, (* On the Sparc, all arguments to C functions, even floating-point arguments,
are passed in %o..%o5, then on the stack *) are passed in %o0..%o5, then on the stack *)
let loc_external_arguments arg = let loc_external_arguments arg =
let loc = Array.new (Array.length arg) Reg.dummy in let loc = Array.new (Array.length arg) Reg.dummy in
@ -244,10 +270,6 @@ let oper_latency = function
Ireload -> 3 Ireload -> 3
| Iload(_, _) -> 3 | Iload(_, _) -> 3
| Iconst_float _ -> 3 (* turned into a load *) | Iconst_float _ -> 3 (* turned into a load *)
| Iintop Imul -> 10
| Iintop_imm(Imul, _) -> 10
| Iintop(Idiv | Imod) -> 20
| Iintop_imm((Idiv | Imod), _) -> 20
| Iaddf | Isubf -> 3 | Iaddf | Isubf -> 3
| Imulf -> 5 | Imulf -> 5
| Idivf -> 15 | Idivf -> 15