cmmgen: compilation des decalages a droite.
selection: merge des resultats des branches d'un switch. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@99 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
736e736a4a
commit
774ee4e145
|
@ -360,9 +360,11 @@ let rec transl = function
|
|||
| Uprim(Plslint, [arg1; arg2]) ->
|
||||
incr_int(Cop(Clsl, [decr_int(transl arg1); untag_int(transl arg2)]))
|
||||
| Uprim(Plsrint, [arg1; arg2]) ->
|
||||
incr_int(Cop(Clsr, [decr_int(transl arg1); untag_int(transl arg2)]))
|
||||
Cop(Cor, [Cop(Clsr, [decr_int(transl arg1); untag_int(transl arg2)]);
|
||||
Cconst_int 1])
|
||||
| Uprim(Pasrint, [arg1; arg2]) ->
|
||||
incr_int(Cop(Casr, [decr_int(transl arg1); untag_int(transl arg2)]))
|
||||
Cop(Cor, [Cop(Casr, [decr_int(transl arg1); untag_int(transl arg2)]);
|
||||
Cconst_int 1])
|
||||
| Uprim(Pintcomp cmp, [arg1; arg2]) ->
|
||||
tag_int(Cop(Ccmpi(transl_comparison cmp), [transl arg1; transl arg2]))
|
||||
| Uprim(Poffsetint n, [arg]) ->
|
||||
|
@ -480,17 +482,18 @@ let rec transl = function
|
|||
Ccatch(transl body, transl handler)
|
||||
| Utrywith(body, exn, handler) ->
|
||||
Ctrywith(transl body, exn, transl handler)
|
||||
| Uifthenelse(Uprim(Pnot, [arg]), ifso, ifnot) ->
|
||||
transl (Uifthenelse(arg, ifnot, ifso))
|
||||
| Uifthenelse(cond, ifso, Ustaticfail) ->
|
||||
exit_if_false cond (transl ifso)
|
||||
| Uifthenelse(cond, Ustaticfail, ifnot) ->
|
||||
exit_if_true cond (transl ifnot)
|
||||
| Uifthenelse(Uprim(Psequand, _) as cond, ifso, ifnot) ->
|
||||
Ccatch(exit_if_false cond (transl ifso), transl ifnot)
|
||||
| Uifthenelse(Uprim(Psequor, _) as cond, ifso, ifnot) ->
|
||||
Ccatch(exit_if_true cond (transl ifnot), transl ifso)
|
||||
| Uifthenelse(cond, ifso, ifnot) ->
|
||||
begin match cond with
|
||||
Uprim(Pnot, [arg]) ->
|
||||
transl (Uifthenelse(arg, ifnot, ifso))
|
||||
| Uprim(Psequand, _) ->
|
||||
Ccatch(exit_if_false cond (transl ifso), transl ifnot)
|
||||
| Uprim(Psequor, _) ->
|
||||
Ccatch(exit_if_true cond (transl ifnot), transl ifso)
|
||||
| _ ->
|
||||
Cifthenelse(test_bool(transl cond), transl ifso, transl ifnot)
|
||||
end
|
||||
Cifthenelse(test_bool(transl cond), transl ifso, transl ifnot)
|
||||
| Usequence(exp1, exp2) ->
|
||||
Csequence(remove_unit(transl exp1), transl exp2)
|
||||
| Uwhile(cond, body) ->
|
||||
|
|
|
@ -249,17 +249,23 @@ let join r1 seq1 r2 seq2 =
|
|||
(* Same, for N branches *)
|
||||
|
||||
let join_array rs =
|
||||
let dest = ref [||] in
|
||||
let some_res = ref [||] in
|
||||
for i = 0 to Array.length rs - 1 do
|
||||
let (r, s) = rs.(i) in
|
||||
if Array.length r > 0 then dest := r
|
||||
if Array.length r > 0 then some_res := r
|
||||
done;
|
||||
if Array.length !dest > 0 then
|
||||
let size_res = Array.length !some_res in
|
||||
if size_res = 0 then [||] else begin
|
||||
let res = Array.new size_res Reg.dummy in
|
||||
for i = 0 to size_res - 1 do
|
||||
res.(i) <- Reg.new (!some_res).(i).typ
|
||||
done;
|
||||
for i = 0 to Array.length rs - 1 do
|
||||
let (r, s) = rs.(i) in
|
||||
if Array.length r > 0 then insert_moves r !dest s
|
||||
if Array.length r > 0 then insert_moves r res s
|
||||
done;
|
||||
!dest
|
||||
res
|
||||
end
|
||||
|
||||
(* Add the instructions for the given expression
|
||||
at the end of the given sequence *)
|
||||
|
|
Loading…
Reference in New Issue