@@ -281,13 +281,23 @@ let mode_tuple mode tuple_modes =
281281 let escaping_context = None in
282282 { position; escaping_context; mode; tuple_modes }
283283
284- let mode_argument ~position ~partial_app alloc_mode =
284+ let mode_argument ~funct ~ index ~ position ~partial_app alloc_mode =
285285 let vmode = Value_mode. of_alloc alloc_mode in
286- match position, partial_app with
287- | Nontail , _ | _ , true ->
288- mode_nontail vmode
289- | Tail , false ->
290- mode_tailcall_argument (Value_mode. local_to_regional vmode)
286+ if partial_app then mode_nontail vmode
287+ else match funct.exp_desc, index, position with
288+ | Texp_ident (_, _, {val_kind =
289+ Val_prim {Primitive. prim_name = (" %sequor" | " %sequand" )}},
290+ Id_prim _), 1 , Tail ->
291+ (* The second argument to (&&) and (||) is in
292+ tail position if the call is *)
293+ mode_return (Value_mode. local_to_regional vmode)
294+ | Texp_ident (_ , _ , _ , Id_prim _ ), _ , _ ->
295+ (* Other primitives cannot be tail-called *)
296+ mode_nontail vmode
297+ | _ , _ , Nontail ->
298+ mode_nontail vmode
299+ | _ , _ , Tail ->
300+ mode_tailcall_argument (Value_mode. local_to_regional vmode)
291301
292302let submode ~loc ~env mode expected_mode =
293303 let res =
@@ -5138,20 +5148,22 @@ and type_argument ?explanation ?recarg env (mode : expected_mode) sarg
51385148 unify_exp env texp ty_expected;
51395149 texp
51405150
5141- and type_apply_arg env ~position ~partial_app (lbl , arg ) =
5151+ and type_apply_arg env ~funct ~ index ~ position ~partial_app (lbl , arg ) =
51425152 match arg with
51435153 | Arg (Unknown_arg { sarg; ty_arg; mode_arg } ) ->
51445154 let mode = Alloc_mode. newvar () in
51455155 Alloc_mode. submode_exn mode mode_arg;
5146- let expected_mode = mode_argument ~position ~partial_app mode in
5156+ let expected_mode =
5157+ mode_argument ~funct ~index ~position ~partial_app mode in
51475158 let arg = type_expect env expected_mode sarg (mk_expected ty_arg) in
51485159 if is_optional lbl then
51495160 unify_exp env arg (type_option(newvar() ));
51505161 (lbl, Arg arg)
51515162 | Arg (Known_arg { sarg; ty_arg; ty_arg0; mode_arg; wrapped_in_some } ) ->
51525163 let mode = Alloc_mode. newvar () in
51535164 Alloc_mode. submode_exn mode mode_arg;
5154- let expected_mode = mode_argument ~position ~partial_app mode in
5165+ let expected_mode =
5166+ mode_argument ~funct ~index ~position ~partial_app mode in
51555167 let arg =
51565168 if wrapped_in_some then
51575169 option_some env
@@ -5186,7 +5198,8 @@ and type_application env app_loc expected_mode funct funct_mode sargs =
51865198 submode ~loc: app_loc ~env
51875199 (Value_mode. of_alloc mres) expected_mode;
51885200 let marg =
5189- mode_argument ~position: expected_mode.position ~partial_app: false marg
5201+ mode_argument ~funct ~index: 0 ~position: expected_mode.position
5202+ ~partial_app: false marg
51905203 in
51915204 let exp = type_expect env marg sarg (mk_expected ty_arg) in
51925205 check_partial_application false exp;
@@ -5214,17 +5227,11 @@ and type_application env app_loc expected_mode funct funct_mode sargs =
52145227 collect_apply_args env funct ignore_labels ty (instance ty)
52155228 (Value_mode. regional_to_global_alloc funct_mode) sargs
52165229 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
5230+ let position = expected_mode.position in
52245231 let partial_app = is_partial_apply args in
52255232 let args =
5226- List. map
5227- ( fun arg -> type_apply_arg env ~position ~partial_app arg)
5233+ List. mapi ( fun index arg ->
5234+ type_apply_arg env ~funct ~index ~position ~partial_app arg)
52285235 args
52295236 in
52305237 let ty_ret, mode_ret, args =
0 commit comments