Skip to content

Commit f815bf2

Browse files
lpw25stedolan
authored andcommitted
Add special mode handling for tuples in matches and let bindings (ocaml#38)
* Fix mode in for_multiple_match
1 parent 39f1211 commit f815bf2

File tree

7 files changed

+338
-88
lines changed

7 files changed

+338
-88
lines changed

lambda/matching.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3672,7 +3672,7 @@ let compile_flattened ~scopes repr partial ctx pmh =
36723672
let lam, total = compile_match_nonempty ~scopes repr partial ctx b in
36733673
compile_orhandlers (compile_match ~scopes repr partial) lam total ctx hs
36743674

3675-
let do_for_multiple_match ~scopes loc paraml pat_act_list partial =
3675+
let do_for_multiple_match ~scopes loc paraml mode pat_act_list partial =
36763676
let repr = None in
36773677
let partial = check_partial pat_act_list partial in
36783678
let raise_num, arg, pm1 =
@@ -3686,7 +3686,7 @@ let do_for_multiple_match ~scopes loc paraml pat_act_list partial =
36863686
| Total -> (-1, Default_environment.empty)
36873687
in
36883688
let loc = Scoped_location.of_location ~scopes loc in
3689-
let arg = Lprim (Pmakeblock (0, Immutable, None, Alloc_heap (* FIXME *)),
3689+
let arg = Lprim (Pmakeblock (0, Immutable, None, mode),
36903690
paraml, loc) in
36913691
( raise_num,
36923692
arg,
@@ -3748,8 +3748,8 @@ let bind_opt (v, eo) k =
37483748
| None -> k
37493749
| Some e -> Lambda.bind Strict v e k
37503750

3751-
let for_multiple_match ~scopes loc paraml pat_act_list partial =
3751+
let for_multiple_match ~scopes loc paraml mode pat_act_list partial =
37523752
let v_paraml = List.map param_to_var paraml in
37533753
let paraml = List.map (fun (v, _) -> Lvar v) v_paraml in
37543754
List.fold_right bind_opt v_paraml
3755-
(do_for_multiple_match ~scopes loc paraml pat_act_list partial)
3755+
(do_for_multiple_match ~scopes loc paraml mode pat_act_list partial)

lambda/matching.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ val for_let:
3434
lambda
3535
val for_multiple_match:
3636
scopes:scopes -> Location.t ->
37-
lambda list -> (pattern * lambda) list -> partial ->
37+
lambda list -> alloc_mode -> (pattern * lambda) list -> partial ->
3838
lambda
3939

4040
val for_tupled_function:

lambda/translcore.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1188,8 +1188,9 @@ and transl_match ~scopes e arg pat_expr_list partial =
11881188
match arg, exn_cases with
11891189
| {exp_desc = Texp_tuple argl}, [] ->
11901190
assert (static_handlers = []);
1191+
let mode = transl_value_mode arg.exp_mode in
11911192
Matching.for_multiple_match ~scopes e.exp_loc
1192-
(transl_list ~scopes argl) val_cases partial
1193+
(transl_list ~scopes argl) mode val_cases partial
11931194
| {exp_desc = Texp_tuple argl}, _ :: _ ->
11941195
let val_ids =
11951196
List.map
@@ -1200,9 +1201,10 @@ and transl_match ~scopes e arg pat_expr_list partial =
12001201
argl
12011202
in
12021203
let lvars = List.map (fun (id, _) -> Lvar id) val_ids in
1204+
let mode = transl_value_mode arg.exp_mode in
12031205
static_catch (transl_list ~scopes argl) val_ids
12041206
(Matching.for_multiple_match ~scopes e.exp_loc
1205-
lvars val_cases partial)
1207+
lvars mode val_cases partial)
12061208
| arg, [] ->
12071209
assert (static_handlers = []);
12081210
Matching.for_function ~scopes e.exp_loc

testsuite/tests/typing-local/local.ml

Lines changed: 105 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -701,7 +701,7 @@ Error: This value escapes its region
701701
|}]
702702

703703

704-
704+
(* raised exceptions must be global *)
705705
let no_leak_exn =
706706
use_locally (fun x -> let _exn = local_ Invalid_argument x in "bluh") "blah"
707707
[%%expect{|
@@ -717,6 +717,23 @@ Line 2, characters 66-67:
717717
Error: This value escapes its region
718718
|}]
719719

720+
(* handled exceptions are known to be global *)
721+
let catch (f : unit -> local_ string) =
722+
let a =
723+
match f () with
724+
| _ -> "hello"
725+
| exception (Invalid_argument x) -> x
726+
in
727+
let b =
728+
try let _ = f () in "hello" with
729+
| Invalid_argument x -> x
730+
in
731+
(a, b)
732+
[%%expect{|
733+
val catch : (unit -> local_ string) -> string * string = <fun>
734+
|}]
735+
736+
720737
(* same, but this time the function is allowed to return its argument *)
721738
let use_locally (f : local_ 'a -> local_ 'a) : local_ 'a -> local_ 'a = f
722739
[%%expect{|
@@ -1430,6 +1447,93 @@ Error: Signature mismatch:
14301447
The first is global and the second is not.
14311448
|}]
14321449

1450+
(* Special handling of tuples in matches and let bindings *)
1451+
let escape : string -> unit = fun x -> ()
1452+
1453+
let foo (local_ x) y =
1454+
match x, y with
1455+
| Some _, Some b -> escape b
1456+
| None, _ -> ()
1457+
| pr -> let _, _ = pr in ();;
1458+
[%%expect{|
1459+
val escape : string -> unit = <fun>
1460+
val foo : local_ 'a option -> string option -> unit = <fun>
1461+
|}]
1462+
1463+
let foo (local_ x) y =
1464+
let pr = x, y in
1465+
match pr with
1466+
| Some _, Some b -> escape b
1467+
| None, _ -> ()
1468+
| _ -> ();;
1469+
[%%expect{|
1470+
Line 4, characters 29-30:
1471+
4 | | Some _, Some b -> escape b
1472+
^
1473+
Error: This value escapes its region
1474+
|}]
1475+
1476+
let foo (local_ x) y =
1477+
match x, y with
1478+
| pr ->
1479+
let _, b = pr in
1480+
escape b
1481+
| _ -> ();;
1482+
[%%expect{|
1483+
Line 5, characters 11-12:
1484+
5 | escape b
1485+
^
1486+
Error: This value escapes its region
1487+
|}]
1488+
1489+
let foo p (local_ x) y z =
1490+
let (_, b) as pr =
1491+
if p then x, y else z
1492+
in
1493+
let _, _ = pr in
1494+
escape b;;
1495+
[%%expect{|
1496+
val foo : bool -> local_ 'a -> string -> 'a * string -> unit = <fun>
1497+
|}]
1498+
1499+
let foo p (local_ x) y (local_ z) =
1500+
let _, b =
1501+
if p then x, y else z
1502+
in
1503+
escape b;;
1504+
[%%expect{|
1505+
Line 5, characters 9-10:
1506+
5 | escape b;;
1507+
^
1508+
Error: This value escapes its region
1509+
|}]
1510+
1511+
let foo p (local_ x) y z =
1512+
let a, _ =
1513+
if p then x, y else z
1514+
in
1515+
escape a;;
1516+
[%%expect{|
1517+
Line 5, characters 9-10:
1518+
5 | escape a;;
1519+
^
1520+
Error: This value escapes its region
1521+
|}]
1522+
1523+
let foo p (local_ x) y z =
1524+
let pr =
1525+
if p then x, y else z
1526+
in
1527+
let _, b = pr in
1528+
escape b;;
1529+
[%%expect{|
1530+
Line 6, characters 9-10:
1531+
6 | escape b;;
1532+
^
1533+
Error: This value escapes its region
1534+
|}]
1535+
1536+
14331537
(* In debug mode, Gc.minor () checks for minor heap->local pointers *)
14341538
let () = Gc.minor ()
14351539
[%%expect{|

0 commit comments

Comments
 (0)