summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorBenedikt Meurer <benedikt.meurer@googlemail.com>2012-02-04 09:43:33 +0000
committerBenedikt Meurer <benedikt.meurer@googlemail.com>2012-02-04 09:43:33 +0000
commitfb327a7c2b95973ae6a277a147b9d77c53fcbae4 (patch)
treedfe323b0feb54c9b62a75590f811c2dcfd543913
parent816ac58196282b22c6ac1b66999d85de59fae92b (diff)
Also pass Cmm.memory_chunk to select_addressing.
The rational behind this change is that for the ARM instruction sets, the valid range for address offsets depends on the type of data being loaded or stored. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12120 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--asmcomp/amd64/selection.ml14
-rw-r--r--asmcomp/arm/selection.ml2
-rw-r--r--asmcomp/i386/selection.ml14
-rw-r--r--asmcomp/power/selection.ml2
-rw-r--r--asmcomp/selectgen.ml6
-rw-r--r--asmcomp/selectgen.mli2
-rw-r--r--asmcomp/sparc/selection.ml2
7 files changed, 21 insertions, 21 deletions
diff --git a/asmcomp/amd64/selection.ml b/asmcomp/amd64/selection.ml
index 86c4a9b58..313290d48 100644
--- a/asmcomp/amd64/selection.ml
+++ b/asmcomp/amd64/selection.ml
@@ -121,7 +121,7 @@ method is_immediate n = n <= 0x7FFFFFFF && n >= -0x80000000
method is_immediate_natint n = n <= 0x7FFFFFFFn && n >= -0x80000000n
-method select_addressing exp =
+method select_addressing chunk exp =
let (a, d) = select_addr exp in
(* PR#4625: displacement must be a signed 32-bit immediate *)
if d < -0x8000_0000 || d > 0x7FFF_FFFF
@@ -157,7 +157,7 @@ method! select_operation op args =
match op with
(* Recognize the LEA instruction *)
Caddi | Cadda | Csubi | Csuba ->
- begin match self#select_addressing (Cop(op, args)) with
+ begin match self#select_addressing Word (Cop(op, args)) with
(Iindexed d, _) -> super#select_operation op args
| (Iindexed2 0, _) -> super#select_operation op args
| (addr, arg) -> (Ispecific(Ilea addr), [arg])
@@ -191,7 +191,7 @@ method! select_operation op args =
begin match args with
[loc; Cop(Caddi, [Cop(Cload _, [loc']); Cconst_int n])]
when loc = loc' && self#is_immediate n ->
- let (addr, arg) = self#select_addressing loc in
+ let (addr, arg) = self#select_addressing Word loc in
(Ispecific(Ioffset_loc(n, addr)), [arg])
| _ ->
super#select_operation op args
@@ -202,12 +202,12 @@ method! select_operation op args =
method select_floatarith commutative regular_op mem_op args =
match args with
- [arg1; Cop(Cload (Double|Double_u), [loc2])] ->
- let (addr, arg2) = self#select_addressing loc2 in
+ [arg1; Cop(Cload (Double|Double_u as chunk), [loc2])] ->
+ let (addr, arg2) = self#select_addressing chunk loc2 in
(Ispecific(Ifloatarithmem(mem_op, addr)),
[arg1; arg2])
- | [Cop(Cload (Double|Double_u), [loc1]); arg2] when commutative ->
- let (addr, arg1) = self#select_addressing loc1 in
+ | [Cop(Cload (Double|Double_u as chunk), [loc1]); arg2] when commutative ->
+ let (addr, arg1) = self#select_addressing chunk loc1 in
(Ispecific(Ifloatarithmem(mem_op, addr)),
[arg2; arg1])
| [arg1; arg2] ->
diff --git a/asmcomp/arm/selection.ml b/asmcomp/arm/selection.ml
index bd165898c..084b47f90 100644
--- a/asmcomp/arm/selection.ml
+++ b/asmcomp/arm/selection.ml
@@ -69,7 +69,7 @@ method! regs_for tyv =
method is_immediate n =
n land 0xFF = n || is_immed n 2
-method select_addressing = function
+method select_addressing chunk = function
Cop(Cadda, [arg; Cconst_int n]) when is_offset n ->
(Iindexed n, arg)
| Cop(Cadda, [arg1; Cop(Caddi, [arg2; Cconst_int n])]) when is_offset n ->
diff --git a/asmcomp/i386/selection.ml b/asmcomp/i386/selection.ml
index 2e0f5a737..f25f09007 100644
--- a/asmcomp/i386/selection.ml
+++ b/asmcomp/i386/selection.ml
@@ -168,7 +168,7 @@ method! is_simple_expr e =
| _ ->
super#is_simple_expr e
-method select_addressing exp =
+method select_addressing chunk exp =
match select_addr exp with
(Asymbol s, d) ->
(Ibased(s, d), Ctuple [])
@@ -200,7 +200,7 @@ method! select_operation op args =
match op with
(* Recognize the LEA instruction *)
Caddi | Cadda | Csubi | Csuba ->
- begin match self#select_addressing (Cop(op, args)) with
+ begin match self#select_addressing Word (Cop(op, args)) with
(Iindexed d, _) -> super#select_operation op args
| (Iindexed2 0, _) -> super#select_operation op args
| (addr, arg) -> (Ispecific(Ilea addr), [arg])
@@ -233,7 +233,7 @@ method! select_operation op args =
begin match args with
[loc; Cop(Caddi, [Cop(Cload _, [loc']); Cconst_int n])]
when loc = loc' ->
- let (addr, arg) = self#select_addressing loc in
+ let (addr, arg) = self#select_addressing Word loc in
(Ispecific(Ioffset_loc(n, addr)), [arg])
| _ ->
super#select_operation op args
@@ -250,11 +250,11 @@ method! select_operation op args =
method select_floatarith regular_op reversed_op mem_op mem_rev_op args =
match args with
[arg1; Cop(Cload chunk, [loc2])] ->
- let (addr, arg2) = self#select_addressing loc2 in
+ let (addr, arg2) = self#select_addressing chunk loc2 in
(Ispecific(Ifloatarithmem(chunk_double chunk, mem_op, addr)),
[arg1; arg2])
| [Cop(Cload chunk, [loc1]); arg2] ->
- let (addr, arg1) = self#select_addressing loc1 in
+ let (addr, arg1) = self#select_addressing chunk loc1 in
(Ispecific(Ifloatarithmem(chunk_double chunk, mem_rev_op, addr)),
[arg2; arg1])
| [arg1; arg2] ->
@@ -295,10 +295,10 @@ method select_push exp =
| Cconst_natpointer n -> (Ispecific(Ipush_int n), Ctuple [])
| Cconst_symbol s -> (Ispecific(Ipush_symbol s), Ctuple [])
| Cop(Cload Word, [loc]) ->
- let (addr, arg) = self#select_addressing loc in
+ let (addr, arg) = self#select_addressing Word loc in
(Ispecific(Ipush_load addr), arg)
| Cop(Cload Double_u, [loc]) ->
- let (addr, arg) = self#select_addressing loc in
+ let (addr, arg) = self#select_addressing Double_u loc in
(Ispecific(Ipush_load_float addr), arg)
| _ -> (Ispecific(Ipush), exp)
diff --git a/asmcomp/power/selection.ml b/asmcomp/power/selection.ml
index 7c37f53ba..179548af5 100644
--- a/asmcomp/power/selection.ml
+++ b/asmcomp/power/selection.ml
@@ -52,7 +52,7 @@ inherit Selectgen.selector_generic as super
method is_immediate n = (n <= 32767) && (n >= -32768)
-method select_addressing exp =
+method select_addressing chunk exp =
match select_addr exp with
(Asymbol s, d) ->
(Ibased(s, d), Ctuple [])
diff --git a/asmcomp/selectgen.ml b/asmcomp/selectgen.ml
index 106d42bc2..fdf181166 100644
--- a/asmcomp/selectgen.ml
+++ b/asmcomp/selectgen.ml
@@ -204,7 +204,7 @@ method virtual is_immediate : int -> bool
(* Selection of addressing modes *)
method virtual select_addressing :
- Cmm.expression -> Arch.addressing_mode * Cmm.expression
+ Cmm.memory_chunk -> Cmm.expression -> Arch.addressing_mode * Cmm.expression
(* Default instruction selection for stores (of words) *)
@@ -219,10 +219,10 @@ method select_operation op args =
| (Capply(ty, dbg), _) -> (Icall_ind, args)
| (Cextcall(s, ty, alloc, dbg), _) -> (Iextcall(s, alloc), args)
| (Cload chunk, [arg]) ->
- let (addr, eloc) = self#select_addressing arg in
+ let (addr, eloc) = self#select_addressing chunk arg in
(Iload(chunk, addr), [eloc])
| (Cstore chunk, [arg1; arg2]) ->
- let (addr, eloc) = self#select_addressing arg1 in
+ let (addr, eloc) = self#select_addressing chunk arg1 in
if chunk = Word then begin
let (op, newarg2) = self#select_store addr arg2 in
(op, [newarg2; eloc])
diff --git a/asmcomp/selectgen.mli b/asmcomp/selectgen.mli
index 73309bf7b..058f9e73e 100644
--- a/asmcomp/selectgen.mli
+++ b/asmcomp/selectgen.mli
@@ -26,7 +26,7 @@ class virtual selector_generic : object
(* Must be defined to indicate whether a constant is a suitable
immediate operand to arithmetic instructions *)
method virtual select_addressing :
- Cmm.expression -> Arch.addressing_mode * Cmm.expression
+ Cmm.memory_chunk -> Cmm.expression -> Arch.addressing_mode * Cmm.expression
(* Must be defined to select addressing modes *)
method is_simple_expr: Cmm.expression -> bool
(* Can be overridden to reflect special extcalls known to be pure *)
diff --git a/asmcomp/sparc/selection.ml b/asmcomp/sparc/selection.ml
index 1dfc06f27..e82cc670a 100644
--- a/asmcomp/sparc/selection.ml
+++ b/asmcomp/sparc/selection.ml
@@ -26,7 +26,7 @@ inherit Selectgen.selector_generic as super
method is_immediate n = (n <= 4095) && (n >= -4096)
-method select_addressing = function
+method select_addressing chunk = function
Cconst_symbol s ->
(Ibased(s, 0), Ctuple [])
| Cop(Cadda, [Cconst_symbol s; Cconst_int n]) ->