diff options
-rw-r--r-- | asmcomp/sparc/arch.ml | 6 | ||||
-rw-r--r-- | asmcomp/sparc/emit.mlp | 26 | ||||
-rw-r--r-- | asmcomp/sparc/selection.ml | 43 |
3 files changed, 11 insertions, 64 deletions
diff --git a/asmcomp/sparc/arch.ml b/asmcomp/sparc/arch.ml index 13a5ca6fc..c4ba9d5ed 100644 --- a/asmcomp/sparc/arch.ml +++ b/asmcomp/sparc/arch.ml @@ -22,7 +22,6 @@ type specific_operation = unit (* None worth mentioning *) type addressing_mode = Ibased of string * int (* symbol + displ *) | Iindexed of int (* reg + displ *) - | Iindexed2 of int (* reg + reg + displ *) (* Sizes, endianness *) @@ -40,12 +39,10 @@ let offset_addressing addr delta = match addr with Ibased(s, n) -> Ibased(s, n + delta) | Iindexed n -> Iindexed(n + delta) - | Iindexed2 n -> Iindexed2(n + delta) let num_args_addressing = function Ibased(s, n) -> 0 | Iindexed n -> 1 - | Iindexed2 n -> 2 (* Printing operations and addressing modes *) @@ -57,9 +54,6 @@ let print_addressing printreg addr arg = | Iindexed n -> printreg arg.(0); if n <> 0 then begin print_string " + "; print_int n end - | Iindexed2 n -> - printreg arg.(0); print_string " + "; printreg arg.(1); - if n <> 0 then begin print_string " + "; print_int n end let print_specific_operation printreg op arg = Misc.fatal_error "Arch_sparc.print_specific_operation" diff --git a/asmcomp/sparc/emit.mlp b/asmcomp/sparc/emit.mlp index 888c279d7..a83219933 100644 --- a/asmcomp/sparc/emit.mlp +++ b/asmcomp/sparc/emit.mlp @@ -115,18 +115,6 @@ let emit_load instr addr arg dst = ` or %g1, %lo({emit_int ofs}), %g1\n`; ` {emit_string instr} [{emit_reg arg.(0)} + %g1], {emit_reg dst}\n` end - | Iindexed2 ofs -> - if ofs = 0 then - ` {emit_string instr} [{emit_reg arg.(0)} + {emit_reg arg.(1)}], {emit_reg dst}\n` - else if is_immediate ofs then begin - ` add {emit_reg arg.(1)}, {emit_int ofs}, %g1\n`; - ` {emit_string instr} [{emit_reg arg.(0)} + %g1], {emit_reg dst}\n` - end else begin - ` sethi %hi({emit_int ofs}), %g1\n`; - ` or %g1, %lo({emit_int ofs}), %g1\n`; - ` add {emit_reg arg.(1)}, %g1, %g1\n`; - ` {emit_string instr} [{emit_reg arg.(0)} + %g1], {emit_reg dst}\n` - end (* Output a store *) @@ -146,18 +134,6 @@ let emit_store instr addr arg src = ` or %g1, %lo({emit_int ofs}), %g1\n`; ` {emit_string instr} {emit_reg src}, [{emit_reg arg.(1)} + %g1]\n` end - | Iindexed2 ofs -> - if ofs = 0 then - ` {emit_string instr} {emit_reg src}, [{emit_reg arg.(1)} + {emit_reg arg.(2)}]\n` - else if is_immediate ofs then begin - ` add {emit_reg arg.(2)}, {emit_int ofs}, %g1\n`; - ` {emit_string instr} {emit_reg src}, [{emit_reg arg.(1)} + %g1]\n` - end else begin - ` sethi %hi({emit_int ofs}), %g1\n`; - ` or %g1, %lo({emit_int ofs}), %g1\n`; - ` add {emit_reg arg.(2)}, %g1, %g1\n`; - ` {emit_string instr} {emit_reg src}, [{emit_reg arg.(1)} + %g1]\n` - end (* Record live pointers at call points *) @@ -550,9 +526,7 @@ let is_one_instr i = | Iconst_int n -> is_native_immediate n | Istackoffset _ -> true | Iload(_, Iindexed n) -> i.res.(0).typ <> Float & is_immediate n - | Iload(_, Iindexed2 n) -> i.res.(0).typ <> Float & n = 0 | Istore(_, Iindexed n) -> i.arg.(0).typ <> Float & is_immediate n - | Istore(_, Iindexed2 n) -> i.arg.(0).typ <> Float & n = 0 | Iintop(op) -> is_one_instr_op op | Iintop_imm(op, _) -> is_one_instr_op op | Iaddf | Isubf | Imulf | Idivf -> true diff --git a/asmcomp/sparc/selection.ml b/asmcomp/sparc/selection.ml index cef4d7c11..60ad6db32 100644 --- a/asmcomp/sparc/selection.ml +++ b/asmcomp/sparc/selection.ml @@ -19,44 +19,23 @@ open Reg open Arch open Mach -(* Recognition of addressing modes *) - -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]) -> - let (a, n) = select_addr arg in (a, n + m) - | Cop((Caddi | Cadda), [Cconst_int m; arg]) -> - let (a, n) = select_addr arg in (a, n + m) - | Cop((Caddi | Cadda), [arg1; arg2]) -> - begin match (select_addr arg1, select_addr arg2) with - ((Alinear e1, n1), (Alinear e2, n2)) -> - (Aadd(e1, e2), n1 + n2) - | _ -> - (Aadd(arg1, arg2), 0) - end - | exp -> - (Alinear exp, 0) - class selector = object (self) inherit Selectgen.selector_generic as super method is_immediate n = (n <= 4095) && (n >= -4096) -method select_addressing exp = - match select_addr exp with - (Asymbol s, d) -> - (Ibased(s, d), Ctuple []) - | (Alinear e, d) -> - (Iindexed d, e) - | (Aadd(e1, e2), d) -> - (Iindexed2 d, Ctuple[e1; e2]) +method select_addressing = function + Cconst_symbol s -> + (Ibased(s, 0), Ctuple []) + | Cop(Cadda, [Cconst_symbol s; Cconst_int n]) -> + (Ibased(s, n), Ctuple []) + | Cop(Cadda, [arg; Cconst_int n]) -> + (Iindexed n, arg) + | Cop(Cadda, [arg1; Cop(Caddi, [arg2; Cconst_int n])]) -> + (Iindexed n, Cop(Cadda, [arg1; arg2])) + | arg -> + (Iindexed 0, arg) method select_operation op args = match (op, args) with |