summaryrefslogtreecommitdiffstats
path: root/asmcomp/sparc
diff options
context:
space:
mode:
Diffstat (limited to 'asmcomp/sparc')
-rw-r--r--asmcomp/sparc/CSE.ml30
-rw-r--r--asmcomp/sparc/emit.mlp14
-rw-r--r--asmcomp/sparc/proc.ml19
3 files changed, 53 insertions, 10 deletions
diff --git a/asmcomp/sparc/CSE.ml b/asmcomp/sparc/CSE.ml
new file mode 100644
index 000000000..e48d60436
--- /dev/null
+++ b/asmcomp/sparc/CSE.ml
@@ -0,0 +1,30 @@
+(***********************************************************************)
+(* *)
+(* OCaml *)
+(* *)
+(* Xavier Leroy, projet Gallium, INRIA Rocquencourt *)
+(* *)
+(* Copyright 2014 Institut National de Recherche en Informatique et *)
+(* en Automatique. All rights reserved. This file is distributed *)
+(* under the terms of the Q Public License version 1.0. *)
+(* *)
+(***********************************************************************)
+
+(* CSE for Sparc *)
+
+open Mach
+open CSEgen
+
+class cse = object (self)
+
+inherit cse_generic (* as super *)
+
+method! is_cheap_operation op =
+ match op with
+ | Iconst_int n | Iconst_blockheader n -> n <= 4095n && n >= -4096n
+ | _ -> false
+
+end
+
+let fundecl f =
+ (new cse)#fundecl f
diff --git a/asmcomp/sparc/emit.mlp b/asmcomp/sparc/emit.mlp
index 12d60ed32..877a3d52a 100644
--- a/asmcomp/sparc/emit.mlp
+++ b/asmcomp/sparc/emit.mlp
@@ -190,7 +190,7 @@ let emit_frame fd =
(* Record floating-point constants *)
-let float_constants = ref ([] : (int * string) list)
+let float_constants = ref ([] : (int * int64) list)
let emit_float_constant (lbl, cst) =
rodata ();
@@ -309,11 +309,11 @@ let rec emit_instr i dslot =
` sethi %hi({emit_nativeint n}), %g1\n`;
` or %g1, %lo({emit_nativeint n}), {emit_reg i.res.(0)}\n`
end
- | Lop(Iconst_float s) ->
+ | Lop(Iconst_float f) ->
(* On UltraSPARC, the fzero instruction could be used to set a
floating point register pair to zero. *)
let lbl = new_label() in
- float_constants := (lbl, s) :: !float_constants;
+ float_constants := (lbl, Int64.bits_of_float f) :: !float_constants;
` sethi %hi({emit_label lbl}), %g1\n`;
` ldd [%g1 + %lo({emit_label lbl})], {emit_reg i.res.(0)}\n`
| Lop(Iconst_symbol s) ->
@@ -375,7 +375,7 @@ let rec emit_instr i dslot =
| _ -> "ld" in
emit_load loadinstr addr i.arg dest
end
- | Lop(Istore(chunk, addr)) ->
+ | Lop(Istore(chunk, addr, _)) ->
let src = i.arg.(0) in
begin match chunk with
Double_u ->
@@ -612,7 +612,7 @@ let is_one_instr i =
| Iconst_int n | Iconst_blockheader n -> is_native_immediate n
| Istackoffset _ -> true
| Iload(_, Iindexed n) -> i.res.(0).typ <> Float && is_immediate n
- | Istore(_, Iindexed n) -> i.arg.(0).typ <> Float && is_immediate n
+ | Istore(_, Iindexed n, _) -> i.arg.(0).typ <> Float && is_immediate n
| Iintop(op) -> is_one_instr_op op
| Iintop_imm(op, _) -> is_one_instr_op op
| Iaddf | Isubf | Imulf | Idivf -> true
@@ -706,9 +706,9 @@ let emit_item = function
| Cint n ->
` .word {emit_nativeint n}\n`
| Csingle f ->
- emit_float32_directive ".word" f
+ emit_float32_directive ".word" (Int32.bits_of_float f)
| Cdouble f ->
- emit_float64_split_directive ".word" f
+ emit_float64_split_directive ".word" (Int64.bits_of_float f)
| Csymbol_address s ->
` .word {emit_symbol s}\n`
| Clabel_address lbl ->
diff --git a/asmcomp/sparc/proc.ml b/asmcomp/sparc/proc.ml
index ed107a82a..625f517f6 100644
--- a/asmcomp/sparc/proc.ml
+++ b/asmcomp/sparc/proc.ml
@@ -81,12 +81,12 @@ let rotate_registers = true
(* Representation of hard registers by pseudo-registers *)
let hard_int_reg =
- let v = Array.create 19 Reg.dummy in
+ let v = Array.make 19 Reg.dummy in
for i = 0 to 18 do v.(i) <- Reg.at_location Int (Reg i) done;
v
let hard_float_reg =
- let v = Array.create 32 Reg.dummy in
+ let v = Array.make 32 Reg.dummy in
for i = 0 to 31 do v.(i) <- Reg.at_location Float (Reg(100 + i)) done;
v
@@ -105,7 +105,7 @@ let stack_slot slot ty =
let calling_conventions first_int last_int first_float last_float make_stack
arg =
- let loc = Array.create (Array.length arg) Reg.dummy in
+ let loc = Array.make (Array.length arg) Reg.dummy in
let int = ref first_int in
let float = ref first_float in
let ofs = ref 0 in
@@ -171,6 +171,10 @@ let loc_external_results res =
let loc_exn_bucket = phys_reg 0 (* $o0 *)
+(* Volatile registers: none *)
+
+let regs_are_volatile rs = false
+
(* Registers destroyed by operations *)
let destroyed_at_c_call = (* %l0-%l4, %i0-%i5 preserved *)
@@ -196,6 +200,15 @@ let max_register_pressure = function
Iextcall(_, _) -> [| 11; 0 |]
| _ -> [| 19; 15 |]
+(* Pure operations (without any side effect besides updating their result
+ registers). *)
+
+let op_is_pure = function
+ | Icall_ind | Icall_imm _ | Itailcall_ind | Itailcall_imm _
+ | Iextcall _ | Istackoffset _ | Istore _ | Ialloc _
+ | Iintop(Icheckbound) | Iintop_imm(Icheckbound, _) -> false
+ | _ -> true
+
(* Layout of the stack *)
let num_stack_slots = [| 0; 0 |]