Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
20 changes: 12 additions & 8 deletions lib/compiler/src/beam_call_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1186,18 +1186,22 @@ lists_map_type_1(_, ElementType) ->

lists_mapfold_type(Fun, Init, List) ->
case {meet(Fun, #t_fun{type=#t_tuple{size=2}}), meet(List, #t_list{})} of
{_, nil} ->
make_two_tuple(nil, Init);
{#t_fun{type=#t_tuple{elements=Es}}, ListType} ->
{#t_fun{type=T}, ListType} when T =/= none ->
#t_tuple{elements=Es} = normalize(T),
ElementType = beam_types:get_tuple_element(1, Es),
AccType = beam_types:get_tuple_element(2, Es),
lists_mapfold_type_1(ListType, ElementType, Init, AccType);
{#t_fun{type=none}, #t_list{}} ->
%% The fun never returns, so the only way we could return normally
%% is if the list is empty, in which case we'll return [] and the
%% initial value.
{_, #t_list{}} ->
%% The fun never returns, or is not a fun. The only way this can
%% succeed is if the given list is empty, in which case we'll
%% return [] and the initial value.
make_two_tuple(nil, Init);
_ ->
{_, nil} ->
make_two_tuple(nil, Init);
{_, _} ->
%% The fun never returns, or is not a fun, and the list is either
%% not a list or is guaranteed not to be empty. This will never
%% return.
none
end.

Expand Down
25 changes: 24 additions & 1 deletion lib/compiler/test/beam_type_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,8 @@
cons/1,tuple/1,
record_float/1,binary_float/1,float_compare/1,float_overflow/1,
arity_checks/1,elixir_binaries/1,find_best/1,
test_size/1,cover_lists_functions/1,list_append/1,bad_binary_unit/1,
test_size/1,cover_lists_functions/1,list_append/1,lists_mapfold/1,
bad_binary_unit/1,
none_argument/1,success_type_oscillation/1,type_subtraction/1,
container_subtraction/1,is_list_opt/1,connected_tuple_elements/1,
switch_fail_inference/1,failures/1,
Expand Down Expand Up @@ -60,6 +61,7 @@ groups() ->
test_size,
cover_lists_functions,
list_append,
lists_mapfold,
bad_binary_unit,
none_argument,
success_type_oscillation,
Expand Down Expand Up @@ -978,6 +980,27 @@ list_append(_Config) ->
hello = id([]) ++ id(hello),
ok.

%% GH-10354: Type inference broke when the fun passed to mapfoldl/mapfoldr
%% returned a union of 2-tuples.
lists_mapfold(_Config) ->
expected_result = id(lists_mapfold_1()),
ok.

lists_mapfold_1() ->
List = [{key,[{number,1}]}],
{_, FinalAcc} =
lists:mapfoldl(
fun({_, PropListItem}, Acc) ->
Number = proplists:get_value(number, PropListItem),
case Number > 0 of
true ->
{false, Acc ++ [expected_result]};
_ ->
{true, Acc}
end
end, [], List),
hd(FinalAcc).

%% OTP-15872: The compiler would treat the "Unit" of bs_init instructions as
%% the unit of the result instead of the required unit of the input, causing
%% is_binary checks to be wrongly optimized away.
Expand Down
Loading