File tree Expand file tree Collapse file tree 8 files changed +19
-7
lines changed
testsuite/tests/typing-local Expand file tree Collapse file tree 8 files changed +19
-7
lines changed Original file line number Diff line number Diff line change @@ -28,7 +28,7 @@ external shift_left : (int32[@local_opt]) -> int -> (int32[@local_opt]) = "%int3
2828external shift_right : (int32 [@ local_opt]) -> int -> (int32 [@ local_opt]) = " %int32_asr"
2929external shift_right_logical : (int32 [@ local_opt]) -> int -> (int32 [@ local_opt]) = " %int32_lsr"
3030external of_int : int -> (int32 [@ local_opt]) = " %int32_of_int"
31- external to_int : int32 -> int = " %int32_to_int"
31+ external to_int : ( int32 [ @ local_opt]) -> int = " %int32_to_int"
3232external of_float : float -> int32
3333 = " caml_int32_of_float" " caml_int32_of_float_unboxed"
3434 [@@ unboxed] [@@ noalloc]
Original file line number Diff line number Diff line change @@ -128,7 +128,7 @@ external of_int : int -> (int32[@local_opt]) = "%int32_of_int"
128128 (type [int32]). On 64-bit platforms, the argument is taken
129129 modulo 2{^32}. *)
130130
131- external to_int : int32 -> int = " %int32_to_int"
131+ external to_int : ( int32 [ @ local_opt]) -> int = " %int32_to_int"
132132(* * Convert the given 32-bit integer (type [int32]) to an
133133 integer (type [int]). On 32-bit platforms, the 32-bit integer
134134 is taken modulo 2{^31}, i.e. the high-order bit is lost
Original file line number Diff line number Diff line change @@ -28,7 +28,7 @@ external shift_left : (int64[@local_opt]) -> int -> (int64[@local_opt]) = "%int6
2828external shift_right : (int64 [@ local_opt]) -> int -> (int64 [@ local_opt]) = " %int64_asr"
2929external shift_right_logical : (int64 [@ local_opt]) -> int -> (int64 [@ local_opt]) = " %int64_lsr"
3030external of_int : int -> (int64 [@ local_opt]) = " %int64_of_int"
31- external to_int : int64 -> int = " %int64_to_int"
31+ external to_int : ( int64 [ @ local_opt]) -> int = " %int64_to_int"
3232external of_float : float -> int64
3333 = " caml_int64_of_float" " caml_int64_of_float_unboxed"
3434 [@@ unboxed] [@@ noalloc]
Original file line number Diff line number Diff line change @@ -126,7 +126,7 @@ external of_int : int -> (int64[@local_opt]) = "%int64_of_int"
126126(* * Convert the given integer (type [int]) to a 64-bit integer
127127 (type [int64]). *)
128128
129- external to_int : int64 -> int = " %int64_to_int"
129+ external to_int : ( int64 [ @ local_opt]) -> int = " %int64_to_int"
130130(* * Convert the given 64-bit integer (type [int64]) to an
131131 integer (type [int]). On 64-bit platforms, the 64-bit integer
132132 is taken modulo 2{^63}, i.e. the high-order bit is lost
Original file line number Diff line number Diff line change @@ -28,7 +28,7 @@ external shift_left: (nativeint[@local_opt]) -> int -> (nativeint[@local_opt]) =
2828external shift_right : (nativeint [@ local_opt]) -> int -> (nativeint [@ local_opt]) = " %nativeint_asr"
2929external shift_right_logical : (nativeint [@ local_opt]) -> int -> (nativeint [@ local_opt]) = " %nativeint_lsr"
3030external of_int : int -> (nativeint [@ local_opt]) = " %nativeint_of_int"
31- external to_int : nativeint -> int = " %nativeint_to_int"
31+ external to_int : ( nativeint [ @ local_opt]) -> int = " %nativeint_to_int"
3232external of_float : float -> nativeint
3333 = " caml_nativeint_of_float" " caml_nativeint_of_float_unboxed"
3434 [@@ unboxed] [@@ noalloc]
Original file line number Diff line number Diff line change @@ -147,7 +147,7 @@ external of_int : int -> (nativeint[@local_opt]) = "%nativeint_of_int"
147147(* * Convert the given integer (type [int]) to a native integer
148148 (type [nativeint]). *)
149149
150- external to_int : nativeint -> int = " %nativeint_to_int"
150+ external to_int : ( nativeint [ @ local_opt]) -> int = " %nativeint_to_int"
151151(* * Convert the given native integer (type [nativeint]) to an
152152 integer (type [int]). The high-order bit is lost during
153153 the conversion. *)
Original file line number Diff line number Diff line change @@ -1713,6 +1713,12 @@ let intf (local_ x) = x |> Int.succ |> Int.add 42 |> pred |> (/) 100 |> (+) 1
17131713val intf : local_ int -> int = <fun>
17141714|}]
17151715
1716+ (* primitives don't count as tail calls, so you can pass them locals *)
1717+ let primloc x = let local_ y = Int32.add x 1l in Int32.to_int y
1718+ [%%expect{|
1719+ val primloc : int32 -> int = <fun>
1720+ |}]
1721+
17161722(* mode-crossing using unary + *)
17171723let promote (local_ x) = +x
17181724[%%expect{|
Original file line number Diff line number Diff line change @@ -5214,7 +5214,13 @@ and type_application env app_loc expected_mode funct funct_mode sargs =
52145214 collect_apply_args env funct ignore_labels ty (instance ty)
52155215 (Value_mode. regional_to_global_alloc funct_mode) sargs
52165216 in
5217- let position = expected_mode.position in
5217+ let position =
5218+ match funct.exp_desc with
5219+ | Texp_ident (_ , _ , _ , Id_prim _ ) ->
5220+ (* Primitives cannot be tail-called, so their arguments
5221+ need not be mode-restricted *)
5222+ Nontail
5223+ | _ -> expected_mode.position in
52185224 let partial_app = is_partial_apply args in
52195225 let args =
52205226 List. map
You can’t perform that action at this time.
0 commit comments