Still following up on commit 16278.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16282 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2015-07-27 17:25:17 +00:00
parent b71ce51227
commit 66e958ef0f
8 changed files with 28 additions and 28 deletions

View File

@ -63,7 +63,7 @@ let num_register_classes = 3
let register_class r =
match (r.typ, !fpu) with
| Val | Int | Addr, _ -> 0
| (Val | Int | Addr), _ -> 0
| Float, VFPv2 -> 1
| Float, VFPv3_D16 -> 1
| Float, _ -> 2
@ -114,7 +114,7 @@ let calling_conventions
let ofs = ref 0 in
for i = 0 to Array.length arg - 1 do
match arg.(i).typ with
Int | Addr as ty ->
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- phys_reg !int;
incr int

View File

@ -113,12 +113,12 @@ method! is_simple_expr = function
| e -> super#is_simple_expr e
method select_addressing chunk = function
| Cop(Cadda, [arg; Cconst_int n])
| Cop((Cadda | Caddv), [arg; Cconst_int n])
when is_offset chunk n ->
(Iindexed n, arg)
| Cop(Cadda, [arg1; Cop(Caddi, [arg2; Cconst_int n])])
| Cop((Cadda | Caddv as op), [arg1; Cop(Caddi, [arg2; Cconst_int n])])
when is_offset chunk n ->
(Iindexed n, Cop(Cadda, [arg1; arg2]))
(Iindexed n, Cop(op, [arg1; arg2]))
| arg ->
(Iindexed 0, arg)
@ -163,18 +163,18 @@ method select_shift_arith op arithop arithrevop args =
method! select_operation op args =
match (op, args) with
(* Recognize special shift arithmetic *)
((Cadda | Caddi), [arg; Cconst_int n])
((Caddv | Cadda | Caddi), [arg; Cconst_int n])
when n < 0 && self#is_immediate (-n) ->
(Iintop_imm(Isub, -n), [arg])
| ((Cadda | Caddi as op), args) ->
| ((Caddv | Cadda | Caddi as op), args) ->
self#select_shift_arith op Ishiftadd Ishiftadd args
| ((Csuba | Csubi), [arg; Cconst_int n])
| (Csubi, [arg; Cconst_int n])
when n < 0 && self#is_immediate (-n) ->
(Iintop_imm(Iadd, -n), [arg])
| ((Csuba | Csubi), [Cconst_int n; arg])
| (Csubi, [Cconst_int n; arg])
when self#is_immediate n ->
(Ispecific(Irevsubimm n), [arg])
| ((Csuba | Csubi as op), args) ->
| (Csubi as op, args) ->
self#select_shift_arith op Ishiftsub Ishiftsubrev args
| (Cand as op, args) ->
self#select_shift_arith op Ishiftand Ishiftand args

View File

@ -111,7 +111,7 @@ let calling_conventions
let ofs = ref 0 in
for i = 0 to Array.length arg - 1 do
match arg.(i).typ with
Int | Addr as ty ->
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- phys_reg !int;
incr int

View File

@ -102,15 +102,15 @@ method! is_simple_expr = function
| e -> super#is_simple_expr e
method select_addressing chunk = function
| Cop(Cadda, [Cconst_symbol s; Cconst_int n])
| Cop((Caddv | Cadda), [Cconst_symbol s; Cconst_int n])
when use_direct_addressing s ->
(Ibased(s, n), Ctuple [])
| Cop(Cadda, [arg; Cconst_int n])
| Cop((Caddv | Cadda), [arg; Cconst_int n])
when is_offset chunk n ->
(Iindexed n, arg)
| Cop(Cadda, [arg1; Cop(Caddi, [arg2; Cconst_int n])])
| Cop((Caddv | Cadda as op), [arg1; Cop(Caddi, [arg2; Cconst_int n])])
when is_offset chunk n ->
(Iindexed n, Cop(Cadda, [arg1; arg2]))
(Iindexed n, Cop(op, [arg1; arg2]))
| Cconst_symbol s
when use_direct_addressing s ->
(Ibased(s, 0), Ctuple [])
@ -120,7 +120,7 @@ method select_addressing chunk = function
method! select_operation op args =
match op with
(* Integer addition *)
| Caddi | Cadda ->
| Caddi | Caddv | Cadda ->
begin match args with
(* Add immediate *)
| [arg; Cconst_int n] | [Cconst_int n; arg] when self#is_immediate n ->
@ -149,7 +149,7 @@ method! select_operation op args =
super#select_operation op args
end
(* Integer subtraction *)
| Csubi | Csuba ->
| Csubi ->
begin match args with
(* Sub immediate *)
| [arg; Cconst_int n] when self#is_immediate n ->

View File

@ -108,7 +108,7 @@ let calling_conventions
let ofs = ref stack_ofs in
for i = 0 to Array.length arg - 1 do
match arg.(i).typ with
Int | Addr as ty ->
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- phys_reg !int;
incr int
@ -162,7 +162,7 @@ let poweropen_external_conventions first_int last_int
let ofs = ref (14 * size_addr) in
for i = 0 to Array.length arg - 1 do
match arg.(i).typ with
Int | Addr as ty ->
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- phys_reg !int;
incr int

View File

@ -26,11 +26,11 @@ type addressing_expr =
let rec select_addr = function
Cconst_symbol s ->
(Asymbol s, 0)
| Cop((Caddi | Cadda), [arg; Cconst_int m]) ->
| Cop((Caddi | Caddv | Cadda), [arg; Cconst_int m]) ->
let (a, n) = select_addr arg in (a, n + m)
| Cop((Caddi | Cadda), [Cconst_int m; arg]) ->
| Cop((Caddi | Caddv | Cadda), [Cconst_int m; arg]) ->
let (a, n) = select_addr arg in (a, n + m)
| Cop((Caddi | Cadda), [arg1; arg2]) ->
| Cop((Caddi | Caddv | Cadda), [arg1; arg2]) ->
begin match (select_addr arg1, select_addr arg2) with
((Alinear e1, n1), (Alinear e2, n2)) ->
(Aadd(e1, e2), n1 + n2)

View File

@ -110,7 +110,7 @@ let calling_conventions first_int last_int first_float last_float make_stack
let ofs = ref 0 in
for i = 0 to Array.length arg - 1 do
match arg.(i).typ with
Int | Addr as ty ->
| Val | Int | Addr as ty ->
if !int <= last_int then begin
loc.(i) <- phys_reg !int;
incr int
@ -150,7 +150,7 @@ let loc_external_arguments arg =
for i = 0 to Array.length arg - 1 do
if !reg <= 5 (* %o5 *) then begin
match arg.(i).typ with
Int | Addr ->
| Val | Int | Addr ->
loc := phys_reg !reg :: !loc;
incr reg
| Float ->

View File

@ -26,12 +26,12 @@ method is_immediate n = (n <= 4095) && (n >= -4096)
method select_addressing chunk = function
Cconst_symbol s ->
(Ibased(s, 0), Ctuple [])
| Cop(Cadda, [Cconst_symbol s; Cconst_int n]) ->
| Cop((Caddv | Cadda), [Cconst_symbol s; Cconst_int n]) ->
(Ibased(s, n), Ctuple [])
| Cop(Cadda, [arg; Cconst_int n]) ->
| Cop((Caddv | Cadda), [arg; Cconst_int n]) ->
(Iindexed n, arg)
| Cop(Cadda, [arg1; Cop(Caddi, [arg2; Cconst_int n])]) ->
(Iindexed n, Cop(Cadda, [arg1; arg2]))
| Cop((Caddv | Cadda as op), [arg1; Cop(Caddi, [arg2; Cconst_int n])]) ->
(Iindexed n, Cop(op, [arg1; arg2]))
| arg ->
(Iindexed 0, arg)