zSystem port: revise addressing modes
- Ibased addressing is removed. The code generated for an Ibased load/store is no better than the code we generate for an Iindexed load/store preceded by a Iconst_symbol instruction that loads the address of the global variable. Plus, we now get opportunities for CSE of the Iconst_symbol. - Iindexed2 addressing is extended with a constant displacement, to take full advantage of the ofs(%r1, %r2) addressing mode of the processor. - During selection instruction, make sure that the constant displacement of Iindexed and Iindexed2 is within range (20 bit signed).master
parent
f6a0392f57
commit
bcb696a260
|
@ -35,17 +35,13 @@ type specific_operation =
|
|||
(* Addressing modes *)
|
||||
|
||||
type addressing_mode =
|
||||
Ibased of string * int (* symbol + displ *)
|
||||
| Iindexed of int (* reg + displ *)
|
||||
| Iindexed2 (* reg + reg *)
|
||||
| Iindexed2 of int (* reg + reg + displ *)
|
||||
|
||||
(* Sizes, endianness *)
|
||||
|
||||
let big_endian = true
|
||||
|
||||
let s390x =
|
||||
match Config.model with "s390x" -> true | _ -> false
|
||||
|
||||
let size_addr = 8
|
||||
let size_int = size_addr
|
||||
let size_float = 8
|
||||
|
@ -62,27 +58,23 @@ let identity_addressing = Iindexed 0
|
|||
|
||||
let offset_addressing addr delta =
|
||||
match addr with
|
||||
Ibased(s, n) -> Ibased(s, n + delta)
|
||||
| Iindexed n -> Iindexed(n + delta)
|
||||
| Iindexed2 -> assert false
|
||||
| Iindexed2 n -> Iindexed2(n + delta)
|
||||
|
||||
let num_args_addressing = function
|
||||
Ibased(s, n) -> 0
|
||||
| Iindexed n -> 1
|
||||
| Iindexed2 -> 2
|
||||
| Iindexed2 n -> 2
|
||||
|
||||
(* Printing operations and addressing modes *)
|
||||
|
||||
let print_addressing printreg addr ppf arg =
|
||||
match addr with
|
||||
| Ibased(s, n) ->
|
||||
let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
|
||||
fprintf ppf "\"%s\"%s" s idx
|
||||
| Iindexed n ->
|
||||
let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
|
||||
fprintf ppf "%a%s" printreg arg.(0) idx
|
||||
| Iindexed2 ->
|
||||
fprintf ppf "%a + %a" printreg arg.(0) printreg arg.(1)
|
||||
| Iindexed2 n ->
|
||||
let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in
|
||||
fprintf ppf "%a + %a%s" printreg arg.(0) printreg arg.(1) idx
|
||||
|
||||
let print_specific_operation printreg op ppf arg =
|
||||
match op with
|
||||
|
|
|
@ -112,32 +112,16 @@ let emit_load_store instr addressing_mode addr n arg =
|
|||
if (compare instr "stey") = 0 then begin
|
||||
` ledbr {emit_fpr 15}, {emit_reg arg}\n`;
|
||||
match addressing_mode with
|
||||
Ibased(s, d) ->
|
||||
if !pic_code then begin
|
||||
` lg {emit_gpr 1}, {emit_symbol s}@GOT({emit_gpr 12})\n`;
|
||||
` {emit_string instr} {emit_fpr 15},{emit_int d}({emit_gpr 1})\n`
|
||||
end else begin
|
||||
` larl {emit_gpr 1}, {emit_symbol_offset (s,d)}\n`;
|
||||
` {emit_string instr} {emit_fpr 15},0({emit_gpr 1})\n`
|
||||
end
|
||||
| Iindexed ofs ->
|
||||
` {emit_string instr} {emit_fpr 15}, {emit_int ofs}({emit_reg addr.(n)})\n`
|
||||
| Iindexed2 ->
|
||||
` {emit_string instr} {emit_fpr 15}, 0({emit_reg addr.(n)},{emit_reg addr.(n+1)})\n`
|
||||
| Iindexed2 ofs ->
|
||||
` {emit_string instr} {emit_fpr 15}, {emit_int ofs}({emit_reg addr.(n)},{emit_reg addr.(n+1)})\n`
|
||||
end else begin
|
||||
match addressing_mode with
|
||||
Ibased(s, d) ->
|
||||
if !pic_code then begin
|
||||
` lg {emit_gpr 1}, {emit_symbol s}@GOT({emit_gpr 12})\n`;
|
||||
` {emit_string instr} {emit_reg arg},{emit_int d}({emit_gpr 1})\n`
|
||||
end else begin
|
||||
` larl {emit_gpr 1}, {emit_symbol_offset (s,d)}\n`;
|
||||
` {emit_string instr} {emit_reg arg},0({emit_gpr 1})\n`
|
||||
end
|
||||
| Iindexed ofs ->
|
||||
` {emit_string instr} {emit_reg arg}, {emit_int ofs}({emit_reg addr.(n)})\n`
|
||||
| Iindexed2 ->
|
||||
` {emit_string instr} {emit_reg arg}, 0({emit_reg addr.(n)},{emit_reg addr.(n+1)})\n`
|
||||
| Iindexed2 ofs ->
|
||||
` {emit_string instr} {emit_reg arg}, {emit_int ofs}({emit_reg addr.(n)},{emit_reg addr.(n+1)})\n`
|
||||
end
|
||||
|
||||
(* After a comparison, extract the result as 0 or 1 *)
|
||||
|
|
|
@ -46,8 +46,6 @@ method reload_retaddr_latency = 12
|
|||
|
||||
method oper_issue_cycles = function
|
||||
Iconst_float _ | Iconst_symbol _ -> 2
|
||||
| Iload(_, Ibased(_, _)) -> 2
|
||||
| Istore(_, Ibased(_, _), _) -> 2
|
||||
| Ialloc _ -> 4
|
||||
| Iintop(Imod) -> 40 (* assuming full stall *)
|
||||
| Iintop(Icomp _) -> 4
|
||||
|
|
|
@ -23,18 +23,15 @@ open Mach
|
|||
exception Use_default
|
||||
|
||||
type addressing_expr =
|
||||
Asymbol of string
|
||||
| Alinear of expression
|
||||
| Aadd of expression * expression
|
||||
|
||||
let rec select_addr = function
|
||||
Cconst_symbol s ->
|
||||
(Asymbol s, 0)
|
||||
| Cop((Caddi | Cadda), [arg; Cconst_int m]) ->
|
||||
| Cop((Caddi | Cadda | Caddv), [arg; Cconst_int m]) ->
|
||||
let (a, n) = select_addr arg in (a, n + m)
|
||||
| Cop((Caddi | Cadda), [Cconst_int m; arg]) ->
|
||||
| Cop((Caddi | Cadda | Caddv), [Cconst_int m; arg]) ->
|
||||
let (a, n) = select_addr arg in (a, n + m)
|
||||
| Cop((Caddi | Cadda), [arg1; arg2]) ->
|
||||
| Cop((Caddi | Cadda | Caddv), [arg1; arg2]) ->
|
||||
begin match (select_addr arg1, select_addr arg2) with
|
||||
((Alinear e1, n1), (Alinear e2, n2)) ->
|
||||
(Aadd(e1, e2), n1 + n2)
|
||||
|
@ -65,15 +62,14 @@ inherit Selectgen.selector_generic as super
|
|||
method is_immediate n = (n <= 2147483647) && (n >= -2147483648)
|
||||
|
||||
method select_addressing chunk exp =
|
||||
match select_addr exp with
|
||||
(Asymbol s, d) ->
|
||||
(Ibased(s, d), Ctuple [])
|
||||
| (Alinear e, d) ->
|
||||
(Iindexed d, e)
|
||||
| (Aadd(e1, e2), d) ->
|
||||
if d = 0
|
||||
then (Iindexed2, Ctuple[e1; e2])
|
||||
else (Iindexed d, Cop(Cadda, [e1; e2]))
|
||||
let (a, d) = select_addr exp in
|
||||
(* 20-bit signed displacement *)
|
||||
if d < 0x80000 && d >= -0x80000 then begin
|
||||
match a with
|
||||
| Alinear e -> (Iindexed d, e)
|
||||
| Aadd(e1, e2) -> (Iindexed2 d, Ctuple [e1; e2])
|
||||
end else
|
||||
(Iindexed 0, exp)
|
||||
|
||||
method! select_operation op args =
|
||||
match (op, args) with
|
||||
|
|
Loading…
Reference in New Issue