summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2008-08-05 13:35:20 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2008-08-05 13:35:20 +0000
commitb1fbba245a51b59a45dc53a74f37a24f5ed5df11 (patch)
treef1a4af7ad864a496856583b8cc4ef1a0bbc3061a
parent5b3cdba5df796c87f730b24b691675b70a8490b7 (diff)
PR#4558 part 1: unboxing of floats and boxed ints across 'let' and similar constructs
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@8981 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--asmcomp/cmmgen.ml18
1 files changed, 16 insertions, 2 deletions
diff --git a/asmcomp/cmmgen.ml b/asmcomp/cmmgen.ml
index a50822fed..83cb1f6e3 100644
--- a/asmcomp/cmmgen.ml
+++ b/asmcomp/cmmgen.ml
@@ -180,8 +180,15 @@ let test_bool = function
let box_float c = Cop(Calloc, [alloc_float_header; c])
-let unbox_float = function
+let rec unbox_float = function
Cop(Calloc, [header; c]) -> c
+ | Clet(id, exp, body) -> Clet(id, exp, unbox_float body)
+ | Cifthenelse(cond, e1, e2) ->
+ Cifthenelse(cond, unbox_float e1, unbox_float e2)
+ | Csequence(e1, e2) -> Csequence(e1, unbox_float e2)
+ | Cswitch(e, tbl, el) -> Cswitch(e, tbl, Array.map unbox_float el)
+ | Ccatch(n, ids, e1, e2) -> Ccatch(n, ids, unbox_float e1, unbox_float e2)
+ | Ctrywith(e1, id, e2) -> Ctrywith(unbox_float e1, id, unbox_float e2)
| c -> Cop(Cload Double_u, [c])
(* Complex *)
@@ -469,7 +476,7 @@ let box_int bi arg =
Cconst_symbol(operations_boxed_int bi);
arg'])
-let unbox_int bi arg =
+let rec unbox_int bi arg =
match arg with
Cop(Calloc, [hdr; ops; Cop(Clsl, [contents; Cconst_int 32])])
when bi = Pint32 && size_int = 8 && big_endian ->
@@ -481,6 +488,13 @@ let unbox_int bi arg =
Cop(Casr, [Cop(Clsl, [contents; Cconst_int 32]); Cconst_int 32])
| Cop(Calloc, [hdr; ops; contents]) ->
contents
+ | Clet(id, exp, body) -> Clet(id, exp, unbox_int bi body)
+ | Cifthenelse(cond, e1, e2) ->
+ Cifthenelse(cond, unbox_int bi e1, unbox_int bi e2)
+ | Csequence(e1, e2) -> Csequence(e1, unbox_int bi e2)
+ | Cswitch(e, tbl, el) -> Cswitch(e, tbl, Array.map (unbox_int bi) el)
+ | Ccatch(n, ids, e1, e2) -> Ccatch(n, ids, unbox_int bi e1, unbox_int bi e2)
+ | Ctrywith(e1, id, e2) -> Ctrywith(unbox_int bi e1, id, unbox_int bi e2)
| _ ->
Cop(Cload(if bi = Pint32 then Thirtytwo_signed else Word),
[Cop(Cadda, [arg; Cconst_int size_addr])])