Premieres adaptations pour l'assembleur GNU
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1666 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
572d7fce33
commit
eec9139cff
|
@ -66,3 +66,10 @@ let print_specific_operation printreg op arg =
|
|||
| Isub4 -> printreg arg.(0); print_string " * 4 - "; printreg arg.(1)
|
||||
| Isub8 -> printreg arg.(0); print_string " * 8 - "; printreg arg.(1)
|
||||
| Ireloadgp _ -> print_string "ldgp"
|
||||
|
||||
(* Distinguish between the Digital assembler and other assemblers (e.g. gas) *)
|
||||
|
||||
let digital_asm =
|
||||
match Config.system with
|
||||
"digital" -> true
|
||||
| _ -> false
|
||||
|
|
|
@ -186,6 +186,10 @@ let emit_addressing addr r n =
|
|||
if ofs > 0 then ` + {emit_int ofs}`;
|
||||
if ofs < 0 then ` - {emit_int(-ofs)}`
|
||||
|
||||
(* Immediate operands *)
|
||||
|
||||
let is_immediate n = digital_asm || (n >= 0 && n <= 255)
|
||||
|
||||
(* Communicate live registers at call points to the assembler *)
|
||||
|
||||
let int_reg_number = [|
|
||||
|
@ -505,12 +509,22 @@ let emit_instr i =
|
|||
` {emit_string instr} {emit_reg i.arg.(0)}, {emit_reg i.arg.(1)}, {emit_reg i.res.(0)}\n`
|
||||
| Lop(Iintop_imm(Idiv, n)) when n = 1 lsl (Misc.log2 n) ->
|
||||
let l = Misc.log2 n in
|
||||
` addq {emit_reg i.arg.(0)}, {emit_int(n-1)}, $25\n`;
|
||||
if is_immediate n then
|
||||
` addq {emit_reg i.arg.(0)}, {emit_int(n-1)}, $25\n`
|
||||
else begin
|
||||
` ldiq $25, {emit_int n}\n`;
|
||||
` addq {emit_reg i.arg.(0)}, $25, $25\n`
|
||||
end;
|
||||
` cmovge {emit_reg i.arg.(0)}, {emit_reg i.arg.(0)}, $25\n`;
|
||||
` sra $25, {emit_int l}, {emit_reg i.res.(0)}\n`
|
||||
| Lop(Iintop_imm(Imod, n)) when n = 1 lsl (Misc.log2 n) ->
|
||||
let l = Misc.log2 n in
|
||||
` and {emit_reg i.arg.(0)}, {emit_int(n-1)}, $25\n`;
|
||||
if is_immediate n then
|
||||
` and {emit_reg i.arg.(0)}, {emit_int(n-1)}, $25\n`;
|
||||
else begin
|
||||
` ldiq $25, {emit_int n}\n`;
|
||||
` and {emit_reg i.arg.(0)}, $25, $25\n`;
|
||||
end;
|
||||
` subq $25, {emit_int n}, $24\n`;
|
||||
` cmovge {emit_reg i.arg.(0)}, $25, $24\n`;
|
||||
` cmoveq $25, $25, $24\n`;
|
||||
|
|
|
@ -11,10 +11,57 @@
|
|||
|
||||
(* $Id$ *)
|
||||
|
||||
open Schedgen (* to create a dependency *)
|
||||
open Mach
|
||||
|
||||
(* No scheduling is needed for the Alpha, the Digital Unix assembler
|
||||
does it better than us. Problem: the assembler for Linux-Alpha
|
||||
does not do scheduling... *)
|
||||
(* The Digital Unix assembler does scheduling better than us.
|
||||
However, the Linux-Alpha assembler does not do scheduling, so we do
|
||||
a feeble attempt here. *)
|
||||
|
||||
let fundecl f = f
|
||||
class scheduler () as self =
|
||||
|
||||
inherit Schedgen.scheduler_generic () as super
|
||||
|
||||
(* Latencies (in cycles). Based on the 21064, with some poetic license. *)
|
||||
|
||||
method oper_latency = function
|
||||
Ireload -> 3
|
||||
| Iload(_, _) -> 3
|
||||
| Iconst_symbol _ -> 3 (* turned into a load *)
|
||||
| Iconst_float _ -> 3 (* turned into a load *)
|
||||
| Iintop(Imul) -> 23
|
||||
| Iintop_imm(Imul, _) -> 23
|
||||
| Iaddf -> 6
|
||||
| Isubf -> 6
|
||||
| Imulf -> 6
|
||||
| Idivf -> 63
|
||||
| _ -> 2
|
||||
(* Most arithmetic instructions can be executed back-to-back in 1 cycle.
|
||||
However, some combinations (arith; load or arith; store) require 2
|
||||
cycles. Also, by claiming 2 cycles instead of 1, we might favor
|
||||
dual issue. *)
|
||||
|
||||
(* Issue cycles. Rough approximations. *)
|
||||
|
||||
method oper_issue_cycles = function
|
||||
Ialloc _ -> 4
|
||||
| Iintop(Icheckbound) -> 2
|
||||
| Iintop_imm(Idiv, _) -> 3
|
||||
| Iintop_imm(Imod, _) -> 5
|
||||
| Iintop_imm(Icheckbound, _) -> 2
|
||||
| Ifloatofint -> 10
|
||||
| Iintoffloat -> 10
|
||||
| _ -> 1
|
||||
|
||||
(* Say that reloadgp is not part of a basic block (prevents moving it
|
||||
past an operation that uses $gp) *)
|
||||
|
||||
method oper_in_basic_block = function
|
||||
Ispecific(Ireloadgp _) -> false
|
||||
| op -> super#oper_in_basic_block op
|
||||
|
||||
end
|
||||
|
||||
let fundecl =
|
||||
if Arch.digital_asm
|
||||
then (fun f -> f)
|
||||
else (new scheduler ())#fundecl
|
||||
|
|
|
@ -23,10 +23,12 @@ class selector () as self =
|
|||
|
||||
inherit Selectgen.selector_generic() as super
|
||||
|
||||
method is_immediate (n : int) = true
|
||||
method is_immediate n = digital_asm || (n >= 0 && n <= 255)
|
||||
|
||||
method select_addressing = function
|
||||
Cconst_symbol s ->
|
||||
(* Force an explicit lda for non-scheduling assemblers,
|
||||
this allows our scheduler to do a better job of it. *)
|
||||
Cconst_symbol s when digital_asm ->
|
||||
(Ibased(s, 0), Ctuple [])
|
||||
| Cop(Cadda, [Cconst_symbol s; Cconst_int n]) ->
|
||||
(Ibased(s, n), Ctuple [])
|
||||
|
|
Loading…
Reference in New Issue