File 0173-beam_validator-Reject-functions-with-more-than-MAX_A.patch of Package erlang
From 0b183d2a3e5c71682b1ae38fe338623c6c853c0a Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 27 Nov 2024 14:54:35 +0100
Subject: [PATCH] beam_validator: Reject functions with more than MAX_ARG
arguments
---
lib/compiler/src/beam_validator.erl | 24 ++++++++--------
lib/compiler/test/beam_validator_SUITE.erl | 29 ++++++++++++++++++--
system/doc/efficiency_guide/system_limits.md | 5 +++-
3 files changed, 43 insertions(+), 15 deletions(-)
diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl
index 791f0bbb5b..9d7d202caf 100644
--- a/lib/compiler/src/beam_validator.erl
+++ b/lib/compiler/src/beam_validator.erl
@@ -82,6 +82,12 @@ format_error({{_M,F,A},{I,Off,Desc}}) ->
" Internal consistency check failed - please report this bug.~n"
" Instruction: ~p~n"
" Error: ~p:~n", [F,A,Off,I,Desc]);
+format_error({{_M,F,A},too_many_arguments}) ->
+ %% The linter rejects user-provided functions that violate this, leaving
+ %% only generated functions like funs or comprehensions. This is not
+ %% super-helpful but it's better than nothing.
+ io_lib:format("System limit reached: generated function ~p/~p has too "
+ "many arguments.", [F, A]);
format_error(Error) ->
io_lib:format("~p~n", [Error]).
@@ -279,17 +285,13 @@ validate_1(Is, MFA0, Entry, Level, Ft) ->
validate_branches(MFA, Vst).
-extract_header([{func_info, {atom,Mod}, {atom,Name}, Arity}=I | Is],
- MFA0, Entry, Offset, Acc) ->
- {_, Name, Arity} = MFA0, %Assertion.
- MFA = {Mod, Name, Arity},
-
- case Is of
- [{label, Entry} | _] ->
- Header = reverse(Acc, [I]),
- {Offset + 1, MFA, Header, Is};
- _ ->
- error({MFA, no_entry_label})
+extract_header([{func_info, {atom, Mod}, {atom,Name}, Arity}=I |
+ [{label, Entry} | _]=Is],
+ {_, Name, Arity}, Entry, Offset, Acc) ->
+ MFA = {Mod, Name, Arity} ,
+ case Arity =< ?MAX_FUNC_ARGS of
+ true -> {Offset + 1, MFA, reverse(Acc, [I]), Is};
+ false -> error({MFA, too_many_arguments})
end;
extract_header([{label,_}=I | Is], MFA, Entry, Offset, Acc) ->
extract_header(Is, MFA, Entry, Offset + 1, [I | Acc]);
diff --git a/lib/compiler/test/beam_validator_SUITE.erl b/lib/compiler/test/beam_validator_SUITE.erl
index c986f66920..0f8c48777a 100644
--- a/lib/compiler/test/beam_validator_SUITE.erl
+++ b/lib/compiler/test/beam_validator_SUITE.erl
@@ -44,7 +44,7 @@
infer_relops/1,
not_equal_inference/1,bad_bin_unit/1,singleton_inference/1,
inert_update_type/1,range_inference/1,
- bif_inference/1,ensure_bits/1]).
+ bif_inference/1,too_many_arguments/1,ensure_bits/1]).
-include_lib("common_test/include/ct.hrl").
@@ -82,7 +82,7 @@ groups() ->
container_performance,infer_relops,
not_equal_inference,bad_bin_unit,singleton_inference,
inert_update_type,range_inference,
- bif_inference,ensure_bits]}].
+ bif_inference,too_many_arguments,ensure_bits]}].
init_per_suite(Config) ->
test_lib:recompile(?MODULE),
@@ -342,7 +342,7 @@ undef_label(Config) when is_list(Config) ->
5},
Errors = beam_val(M),
[{{undef_label,t,1},{undef_labels,[42]}},
- {{undef_label,x,1},no_entry_label}] = Errors,
+ {{undef_label,x,1},invalid_function_header}] = Errors,
ok.
illegal_instruction(Config) when is_list(Config) ->
@@ -1160,6 +1160,29 @@ bif_inference_is_function(A, A) when A orelse ok; is_function(A) ->
bif_inference_is_function(_, _) ->
error.
+%% GH-9113: We didn't reject funs, comprehensions, and the likes which exceeded
+%% the argument limit.
+too_many_arguments(_Config) ->
+ M = {too_many_arguments,
+ [{t,256},{t,0}],
+ [],
+ [{function,t,256,2,
+ [{label,1},
+ {func_info,{atom,too_many_arguments},{atom,t},256},
+ {label,2},
+ return]},
+ {function,t,0,4,
+ [{label,3},
+ %% Mismatching arity.
+ {func_info,{atom,too_many_arguments},{atom,t},5},
+ {label,4},
+ return]}],
+ 5},
+ Errors = beam_val(M),
+ [{{too_many_arguments,t,256},too_many_arguments},
+ {{too_many_arguments,t,0},invalid_function_header}] = Errors,
+ ok.
+
%% GH-9304: Validator did not check that operations were preceded by
%% ensure_at_least / ensure_exactly.
ensure_bits(_Config) ->
diff --git a/system/doc/efficiency_guide/system_limits.md b/system/doc/efficiency_guide/system_limits.md
index 052ceafa00..d6f96bb82e 100644
--- a/system/doc/efficiency_guide/system_limits.md
+++ b/system/doc/efficiency_guide/system_limits.md
@@ -82,7 +82,10 @@ on a 32 bit system at most `2²⁸ - 1`.
open files and sockets depends on [the maximum number of Erlang ports](#ports)
available, as well as on operating system-specific settings and limits.
-- **Number of arguments to a function or fun** - 255.
+- **Number of arguments to a function** - 255.
+
+- **Number of arguments to a fun** - 255, minus one for each environment
+variable.
- [](){: #unique_references } **Unique References on a Runtime System Instance** -
Each scheduler thread has its own set of references, and all other threads have
--
2.43.0