File 3412-Warn-about-exported-variables-from-non-block-constru.patch of Package erlang
From cde236cb7c965099873c5e9d0348aa392d3ece75 Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Sun, 1 Dec 2024 18:22:35 +0100
Subject: [PATCH 2/4] Warn about exported variables from non-block constructs
Placing variable bindings inside the arguments of an expression
can be highly surprising and confusing to the reader. It is very
rarely seen in practice, and it would be best if such uses could
be turned into errors eventually.
---
lib/stdlib/src/erl_lint.erl | 138 ++++++++++++++++++++++++++----------
1 file changed, 100 insertions(+), 38 deletions(-)
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 02a6c511ce..d9cd03c519 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -70,6 +70,7 @@ Module:format_error(ErrorDescriptor)
`m:epp`, `m:erl_parse`
""".
+
-export([module/1,module/2,module/3,format_error/1]).
-export([exprs/2,exprs_opt/3,used_vars/2]). % Used from erl_eval.erl.
-export([is_pattern_expr/1,is_guard_test/1,is_guard_test/2,is_guard_test/3]).
@@ -457,6 +458,15 @@ format_error_1({unbound_var,V,GuessV}) ->
format_error_1({unsafe_var,V,{What,Where}}) ->
{~"variable ~w unsafe in ~w ~s",
[V,What,format_where(Where)]};
+format_error_1({export_var_subexpr,V,{What,Where}}) ->
+ {~"""
+ variable ~w exported from ~w ~s.
+ Exporting bindings from subexpressions other than block expressions is
+ deprecated and may yield an error in a future version of Erlang/OTP.
+ Please move the binding of ~w out of the ~w.
+ Compile directive 'nowarn_export_var_subexpr' can be used to suppress
+ warnings in selected modules.
+ """, [V,What,format_where(Where),V,What]};
format_error_1({exported_var,V,{What,Where}}) ->
{~"variable ~w exported from ~w ~s",
[V,What,format_where(Where)]};
@@ -773,6 +773,9 @@ start(File, Opts) ->
{export_vars,
bool_option(warn_export_vars, nowarn_export_vars,
false, Opts)},
+ {export_var_subexpr,
+ bool_option(warn_export_var_subexpr, nowarn_export_var_subexpr,
+ true, Opts)},
{shadow_vars,
bool_option(warn_shadow_vars, nowarn_shadow_vars,
true, Opts)},
@@ -2711,21 +2722,27 @@ expr({atom,Anno,A}, _Vt, St) ->
{[],keyword_warning(Anno, A, St)};
expr({string,_Anno,_S}, _Vt, St) -> {[],St};
expr({nil,_Anno}, _Vt, St) -> {[],St};
-expr({cons,_Anno,H,T}, Vt, St) ->
- expr_list([H,T], Vt, St);
+expr({cons,Anno,H,T}, Vt, St) ->
+ vtupd_export_expr_list({list, Anno}, [H, T], Vt, St);
expr({lc,_Anno,E,Qs}, Vt, St) ->
handle_comprehension(E, Qs, Vt, St);
expr({bc,_Anno,E,Qs}, Vt, St) ->
handle_comprehension(E, Qs, Vt, St);
expr({mc,_Anno,E,Qs}, Vt, St) ->
handle_comprehension(E, Qs, Vt, St);
-expr({tuple,_Anno,Es}, Vt, St) ->
- expr_list(Es, Vt, St);
-expr({map,_Anno,Es}, Vt, St) ->
- map_fields(Es, Vt, check_assoc_fields(Es, St), fun expr_list/3);
+expr({tuple,Anno,Es}, Vt, St) ->
+ vtupd_export_expr_list({tuple, Anno}, Es, Vt, St);
+expr({map,Anno,Es}, Vt, St) ->
+ map_fields(Es, Vt, check_assoc_fields(Es, St),
+ fun(Es0, Vt0, St0) ->
+ vtupd_export_expr_list({map, Anno}, Es0, Vt0, St0)
+ end);
expr({map,Anno,Src,Es}, Vt, St) ->
- {Svt,St1} = expr(Src, Vt, St),
- {Fvt,St2} = map_fields(Es, Vt, St1, fun expr_list/3),
+ {Svt,St1} = vtupd_export_expr_list({map, Anno}, [Src], Vt, St),
+ {Fvt,St2} = map_fields(Es, Vt, St1,
+ fun(Es0, Vt0, St0) ->
+ vtupd_export_expr_list({map, Anno}, Es0, Vt0, St0)
+ end),
{vtupdate(Svt, Fvt), warn_if_literal_update(Anno, Src, St2)};
expr({record_index,Anno,Name,Field}, _Vt, St) ->
check_record(Anno, Name, St,
@@ -2752,11 +2769,13 @@ expr({record,Anno,Rec,Name,Upds}, Vt, St0) ->
no -> {vtmerge(Rvt, Usvt), warn_if_literal_update(Anno, Rec, St2)};
WildAnno -> {[],add_error(WildAnno, {wildcard_in_update,Name}, St2)}
end;
-expr({bin,_Anno,Fs}, Vt, St) ->
- expr_bin(Fs, Vt, St, fun expr/3);
-expr({block,_Anno,Es}, Vt, St) ->
+expr({bin,Anno,Fs}, Vt, St) ->
+ {Vt1, St1} = expr_bin(Fs, Vt, St, fun expr/3),
+ {vtupd_export({binary, Anno}, Vt1, Vt), St1};
+expr({block,Anno,Es}, Vt, St) ->
%% Unfold block into a sequence.
- exprs(Es, Vt, St);
+ {Vt1, St1} = exprs(Es, Vt, St),
+ {vtupd_export({'begin', Anno}, Vt1, Vt), St1};
expr({'if',Anno,Cs}, Vt, St) ->
icrt_clauses(Cs, {'if',Anno}, Vt, St);
expr({'case',Anno,E,Cs}, Vt, St0) ->
@@ -2828,7 +2847,7 @@ expr({call,Anno,{remote,_Ar,{atom,_Am,M},{atom,Af,F}},As}, Vt, St0) ->
St2 = check_remote_function(Anno, M, F, As, St1),
St3 = check_module_name(M, Anno, St2),
St4 = check_remote_self_call(Anno, M, F, length(As), St3),
- expr_list(As, Vt, St4);
+ vtupd_export_expr_list({call, Anno}, As, Vt, St4);
expr({call,Anno,{remote,_Ar,M,F},As}, Vt, St0) ->
St1 = keyword_warning(Anno, M, St0),
St2 = keyword_warning(Anno, F, St1),
@@ -2861,10 +2864,10 @@ expr({call,Anno,{remote,_Ar,M,F},As}, Vt, St0) ->
_ ->
St2
end,
- expr_list([M,F|As], Vt, St3);
+ vtupd_export_expr_list({call, Anno}, [M, F | As], Vt, St3);
expr({call,Anno,{atom,Aa,F},As}, Vt, St0) ->
St1 = keyword_warning(Aa, F, St0),
- {Asvt,St2} = expr_list(As, Vt, St1),
+ {Asvt,St2} = vtupd_export_expr_list({call, Anno}, As, Vt, St1),
A = length(As),
IsLocal = is_local_function(St2#lint.locals,{F,A}),
IsAutoBif = erl_internal:bif(F, A),
@@ -2919,7 +2922,7 @@ expr({call,Anno,{atom,Aa,F},As}, Vt, St0
end;
expr({call,Anno,F,As}, Vt, St0) ->
St = warn_invalid_call(Anno,F,St0),
- expr_list([F|As], Vt, St); %They see the same variables
+ vtupd_export_expr_list({call, Anno}, [F | As], Vt, St); %They see the same variables
expr({'try',Anno,Es,Scs,Ccs,As}, Vt, St0) ->
%% The only exports we allow are from the try expressions to the
%% success clauses.
@@ -2892,19 +2911,19 @@ expr({'maybe',MaybeAnno,Es,{'else',ElseAnno,Cs}}, Vt, St) ->
Cvt2 = vtmerge(Cvt0, Cvt1),
{vtmerge(Evt2, Cvt2),St2};
%% No comparison or boolean operators yet.
-expr({op,_Anno,_Op,A}, Vt, St) ->
- expr(A, Vt, St);
+expr({op,Anno,Op,A}, Vt, St) ->
+ vtupd_export_expr_list({Op, Anno}, [A], Vt, St);
expr({op,Anno,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
- {Evt1,St1} = expr(L, Vt, St0),
+ {Evt1, St1} = vtupd_export_expr_list({Op, Anno}, [L], Vt, St0),
Vt1 = vtupdate(Evt1, Vt),
{Evt2,St2} = expr(R, Vt1, St1),
Evt3 = vtupd_unsafe({Op, Anno}, Evt2, Vt1),
{vtmerge(Evt1, Evt3),St2};
-expr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
+expr({op,Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
St = expr_check_match_zero(R, expr_check_match_zero(L, St0)),
- expr_list([L,R], Vt, St); %They see the same variables
-expr({op,_Anno,_Op,L,R}, Vt, St) ->
- expr_list([L,R], Vt, St); %They see the same variables
+ vtupd_export_expr_list({EqOp, Anno}, [L, R], Vt, St); %They see the same variables
+expr({op,Anno,Op,L,R}, Vt, St) ->
+ vtupd_export_expr_list({Op, Anno}, [L, R], Vt, St); %They see the same variables
%% The following are not allowed to occur anywhere!
expr({remote,_Anno,M,_F}, _Vt, St) ->
{[],add_error(erl_parse:first_anno(M), illegal_expr, St)};
@@ -2985,6 +3004,12 @@ expr_list(Es, Vt, St0) ->
vtmerge_pat(Evt, Esvt, St2)
end, {[], St0}, Es).
+%% as expr_list but mark new vars as exported
+
+vtupd_export_expr_list(Where, Es, Vt, St) ->
+ {Evt, St1} = expr_list(Es, Vt, St),
+ {vtupd_export(Where, Evt, Vt), St1}.
+
record_expr(Anno, Rec, Vt, St0) ->
St1 = warn_invalid_record(Anno, Rec, St0),
expr(Rec, Vt, St1).
@@ -4313,8 +4338,14 @@ pat_var(V, Anno, Vt, New, St0) ->
{ok,{{export,From},_Usage,Ls}} ->
St = warn_underscore_match(V, Anno, St0),
{[{V,{bound,used,Ls}}],[],
- %% As this is matching, exported vars are risky.
- add_warning(Anno, {exported_var,V,From}, St)};
+ case export_var_subexpr(From) of
+ true ->
+ maybe_add_warning(Anno, {export_var_subexpr,V,From}, St);
+ false ->
+ %% As this is matching, exported vars are risky.
+ %% Always warn unconditionally.
+ add_warning(Anno, {exported_var,V,From}, St)
+ end};
error when St0#lint.recdef_top ->
{[],[{V,{bound,unused,[Anno]}}],
add_error(Anno, {variable_in_record_def,V}, St0)};
@@ -4367,9 +4398,17 @@ pat_binsize_var(V, Anno, Vt, New, St) ->
add_error(Anno, {unsafe_var,V,In}, St)};
{ok,{{export,From},_Used,As}} ->
{[{V,{bound,used,As}}],[],
- %% As this is not matching, exported vars are
- %% probably safe.
- exported_var(Anno, V, From, St)};
+ case export_var_subexpr(From) of
+ true ->
+ maybe_add_warning(Anno, {export_var_subexpr,V,From}, St);
+ false ->
+ %% As this is not matching, exported vars are
+ %% probably safe. The warning is conditional.
+ case is_warn_enabled(export_vars, St) of
+ true -> add_warning(Anno, {exported_var,V,From}, St);
+ false -> St
+ end
+ end};
error ->
PossibleVs = [atom_to_list(DefV) || {DefV, _A} <- Vt],
case most_possible_string(V, PossibleVs) of
@@ -4406,12 +4445,18 @@ do_expr_var(V, Anno, Vt, St) ->
{[{V,{bound,used,As}}],
add_error(Anno, {unsafe_var,V,In}, St)};
{ok,{{export,From},_Usage,As}} ->
- case is_warn_enabled(export_vars, St) of
+ case export_var_subexpr(From) of
true ->
{[{V,{bound,used,As}}],
- add_warning(Anno, {exported_var,V,From}, St)};
+ maybe_add_warning(Anno, {export_var_subexpr,V,From}, St)};
false ->
- {[{V,{{export,From},used,As}}],St}
+ case is_warn_enabled(export_vars, St) of
+ true ->
+ {[{V,{bound,used,As}}],
+ add_warning(Anno, {exported_var,V,From}, St)};
+ false ->
+ {[{V,{{export,From},used,As}}],St}
+ end
end;
{ok,{stacktrace,_Usage,As}} ->
{[{V,{bound,used,As}}],
@@ -4428,11 +4473,14 @@ do_expr_var(V, Anno, Vt, St) ->
end
end.
-exported_var(Anno, V, From, St) ->
- case is_warn_enabled(export_vars, St) of
- true -> add_warning(Anno, {exported_var,V,From}, St);
- false -> St
- end.
+%% warn about exporting from non-block subexpressions
+export_var_subexpr({'begin',_}) -> false;
+export_var_subexpr({'if',_}) -> false;
+export_var_subexpr({'case',_}) -> false;
+export_var_subexpr({'receive',_}) -> false;
+export_var_subexpr({'try',_}) -> false;
+export_var_subexpr({'maybe',_}) -> false;
+export_var_subexpr(_) -> true.
shadow_vars(Vt, Vt0, In, St0) ->
case is_warn_enabled(shadow_vars, St0) of
@@ -4490,15 +4538,29 @@ vtupdate(Uvt, Vt0) ->
end, Uvt, Vt0).
%% vtunsafe(From, UpdVarTable, VarTable) -> UnsafeVarTable.
-%% Return all new variables in UpdVarTable as unsafe.
+%% Mark all new variables in UpdVarTable as unsafe.
vtunsafe({Tag,Anno}, Uvt, Vt) ->
Location = erl_anno:location(Anno),
- [{V,{{unsafe,{Tag,Location}},U,As}} || {V,{_,U,As}} <- vtnew(Uvt, Vt)].
+ vt_mark_new({unsafe,{Tag,Location}}, Uvt, Vt).
vtupd_unsafe(Where, NewVt, OldVt) ->
vtupdate(vtunsafe(Where, NewVt, OldVt), NewVt).
+%% vtexport(From, UpdVarTable, VarTable) -> ExpVarTable.
+%% Mark all new variables in UpdVarTable as exported.
+
+vtexport({Tag, Anno}, Uvt, Vt) ->
+ Location = erl_anno:location(Anno),
+ vt_mark_new({export, {Tag, Location}}, Uvt, Vt).
+
+vtupd_export(Where, NewVt, OldVt) ->
+ vtupdate(vtexport(Where, NewVt, OldVt), NewVt).
+
+vt_mark_new(S, Uvt, Vt) ->
+ [{V, {merge_state(S, S0), U, Ls}}
+ || {V, {S0, U, Ls}} <- vtnew(Uvt, Vt)].
+
%% vtmerge(VarTable, VarTable) -> VarTable.
%% Merge two variables tables generating a new vartable. Give priority to
%% errors then warnings.
--
2.51.0