File 2161-Allow-variables-bound-in-try-to-be-used-in-of-clause.patch of Package erlang
From 8a9a443a454327cbf17120f63664caa0973e9050 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 16 Jun 2020 05:06:23 +0200
Subject: [PATCH] Allow variables bound in 'try' to be used in 'of' clauses
The following program would not compile:
-module(foo).
baz() ->
try Bar = 42 of
_ -> Bar
after
ok
end.
The error message is "foo.erl:4: variable 'Bar' unsafe in 'try' (line 3)".
There is no reason for 'Bar' to be unsafe, because if the pattern
after `of` is reached, `Bar = 42` must have been successfully evaluated.
https://bugs.erlang.org/browse/ERL-1281
---
lib/compiler/src/v3_core.erl | 28 +++++++----
lib/compiler/test/trycatch_SUITE.erl | 73 +++++++++++++++++++++++++++-
lib/stdlib/src/erl_lint.erl | 12 ++---
lib/stdlib/test/erl_lint_SUITE.erl | 5 +-
4 files changed, 97 insertions(+), 21 deletions(-)
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index d318fab15c..8037bb6efc 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -2406,13 +2406,16 @@ uexpr(#icall{anno=A,module=Mod,name=Name,args=As}, _, St) ->
Used = union([lit_vars(Mod),lit_vars(Name),lit_list_vars(As)]),
{#icall{anno=A#a{us=Used},module=Mod,name=Name,args=As},St};
uexpr(#itry{anno=A,args=As0,vars=Vs,body=Bs0,evars=Evs,handler=Hs0}, Ks, St0) ->
- %% Note that we export only from body and exception.
+ %% No variables are exported from try/catch. Starting in OTP 24,
+ %% variables bound in the argument (the code between the 'try' and
+ %% the 'of' keywords) are exported to the body (the code following
+ %% the 'of' keyword).
{As1,St1} = uexprs(As0, Ks, St0),
- {Bs1,St2} = uexprs(Bs0, Ks, St1),
+ ArgKs = union(Ks, new_in_any(As1)),
+ {Bs1,St2} = uexprs(Bs0, ArgKs, St1),
{Hs1,St3} = uexprs(Hs0, Ks, St2),
Used = intersection(used_in_any(Bs1++Hs1++As1), Ks),
- New = new_in_all(Bs1++Hs1),
- {#itry{anno=A#a{us=Used,ns=New},
+ {#itry{anno=A#a{us=Used,ns=[]},
args=As1,vars=Vs,body=Bs1,evars=Evs,handler=Hs1},St3};
uexpr(#icatch{anno=A,body=Es0}, Ks, St0) ->
{Es1,St1} = uexprs(Es0, Ks, St0),
@@ -2833,13 +2836,18 @@ cexpr(#ireceive2{anno=A,clauses=Lcs,timeout=Lto,action=Les}, As, St0) ->
{#c_receive{anno=A#a.anno,
clauses=Ccs,timeout=Cto,action=Ces},
Exp,A#a.us,St3};
-cexpr(#itry{anno=A,args=La,vars=Vs,body=Lb,evars=Evs,handler=Lh}, As, St0) ->
- Exp = intersection(A#a.ns, As), %Exports
- {Ca,_Us1,St1} = cexprs(La, [], St0),
- {Cb,_Us2,St2} = cexprs(Lb, Exp, St1),
- {Ch,_Us3,St3} = cexprs(Lh, Exp, St2),
+cexpr(#itry{anno=A,args=La,vars=Vs0,body=Lb,evars=Evs,handler=Lh}, _As, St0) ->
+ %% No variables are exported from try/catch. Starting in OTP 24,
+ %% variables bound in the argument (the code between the 'try' and
+ %% the 'of' keywords) are exported to the body (the code following
+ %% the 'of' keyword).
+ AsExp = intersection(new_in_any(La), used_in_any(Lb)),
+ {Ca,_Us1,St1} = cexprs(La, AsExp, St0),
+ {Cb,_Us2,St2} = cexprs(Lb, [], St1),
+ {Ch,_Us3,St3} = cexprs(Lh, [], St2),
+ Vs = Vs0 ++ [#c_var{name=V} || V <- AsExp],
{#c_try{anno=A#a.anno,arg=Ca,vars=Vs,body=Cb,evars=Evs,handler=Ch},
- Exp,A#a.us,St3};
+ [],A#a.us,St3};
cexpr(#icatch{anno=A,body=Les}, _As, St0) ->
{Ces,_Us1,St1} = cexprs(Les, [], St0), %Never export!
{#c_catch{body=Ces},[],A#a.us,St1};
diff --git a/lib/compiler/test/trycatch_SUITE.erl b/lib/compiler/test/trycatch_SUITE.erl
index 148969a4d1..630f96349b 100644
--- a/lib/compiler/test/trycatch_SUITE.erl
+++ b/lib/compiler/test/trycatch_SUITE.erl
@@ -29,6 +29,7 @@
hockey/1,handle_info/1,catch_in_catch/1,grab_bag/1,
stacktrace/1,nested_stacktrace/1,raise/1,
no_return_in_try_block/1,
+ expression_export/1,
coverage/1]).
-include_lib("common_test/include/ct.hrl").
@@ -46,7 +47,8 @@ groups() ->
bool,plain_catch_coverage,andalso_orelse,get_in_try,
hockey,handle_info,catch_in_catch,grab_bag,
stacktrace,nested_stacktrace,raise,
- no_return_in_try_block,coverage]}].
+ no_return_in_try_block,expression_export,
+ coverage]}].
init_per_suite(Config) ->
@@ -1383,6 +1385,75 @@ no_return_in_try_block_1(H) ->
no_return() -> throw(no_return).
+expression_export(_Config) ->
+ 42 = expr_export_1(),
+ 42 = expr_export_2(),
+
+ 42 = expr_export_3(fun() -> bar end),
+ beer = expr_export_3(fun() -> pub end),
+ {error,failed} = expr_export_3(fun() -> error(failed) end),
+ is_42 = expr_export_3(fun() -> 42 end),
+ no_good = expr_export_3(fun() -> bad end),
+
+ <<>> = expr_export_4(<<1:32>>),
+ <<"abcd">> = expr_export_4(<<2:32,"abcd">>),
+ no_match = expr_export_4(<<0:32>>),
+ no_match = expr_export_4(<<777:32>>),
+
+ {1,2,3} = expr_export_5(),
+ ok.
+
+expr_export_1() ->
+ try Bar = 42 of
+ _ -> Bar
+ after
+ ok
+ end.
+
+expr_export_2() ->
+ try Bar = 42 of
+ _ -> Bar
+ catch
+ _:_ ->
+ error
+ end.
+
+expr_export_3(F) ->
+ try
+ Bar = 42,
+ F()
+ of
+ bar -> Bar;
+ pub -> beer;
+ Bar -> is_42;
+ _ -> no_good
+ catch
+ error:Reason ->
+ {error,Reason}
+ end.
+
+expr_export_4(Bin) ->
+ try
+ SzSz = id(32),
+ Bin
+ of
+ <<Sz:SzSz,Tail:(4*Sz-4)/binary>> -> Tail;
+ <<_/binary>> -> no_match
+ after
+ ok
+ end.
+
+expr_export_5() ->
+ try
+ X = 1,
+ Z = 3,
+ Y = 2
+ of
+ 2 -> {X,Y,Z}
+ after
+ ok
+ end.
+
coverage(_Config) ->
{'EXIT',{{badfun,true},[_|_]}} = (catch coverage_1()),
ok.
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 886988532f..fe3f1e33a8 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2520,14 +2520,14 @@ expr({call,Line,F,As}, Vt, St0) ->
St = warn_invalid_call(Line,F,St0),
expr_list([F|As], Vt, St); %They see the same variables
expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) ->
- %% Currently, we don't allow any exports because later
- %% passes cannot handle exports in combination with 'after'.
+ %% The only exports we allow are from the try expressions to the
+ %% success clauses.
{Evt0,St1} = exprs(Es, Vt, St0),
TryLine = {'try',Line},
Uvt = vtunsafe(TryLine, Evt0, Vt),
- Evt1 = vtupdate(Uvt, Evt0),
{Sccs,St2} = try_clauses(Scs, Ccs, TryLine,
- vtupdate(Evt1, Vt), St1),
+ vtupdate(Evt0, Vt), Uvt, St1),
+ Evt1 = vtupdate(Uvt, Evt0),
Rvt0 = Sccs,
Rvt1 = vtupdate(vtunsafe(TryLine, Rvt0, Vt), Rvt0),
Evt2 = vtmerge(Evt1, Rvt1),
@@ -3333,10 +3333,10 @@ is_module_dialyzer_option(Option) ->
%% try_catch_clauses(Scs, Ccs, In, ImportVarTable, State) ->
%% {UpdVt,State}.
-try_clauses(Scs, Ccs, In, Vt, St0) ->
+try_clauses(Scs, Ccs, In, Vt, Uvt, St0) ->
{Csvt0,St1} = icrt_clauses(Scs, Vt, St0),
St2 = St1#lint{in_try_head=true},
- {Csvt1,St3} = icrt_clauses(Ccs, Vt, St2),
+ {Csvt1,St3} = icrt_clauses(Ccs, vtupdate(Uvt, Vt), St2),
Csvt = Csvt0 ++ Csvt1,
UpdVt = icrt_export(Csvt, Vt, In, St3),
{UpdVt,St3#lint{in_try_head=false}}.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index aa941e61b6..20f8407f85 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1216,7 +1216,6 @@ unsafe_vars_try(Config) when is_list(Config) ->
[],
{errors,[{5,erl_lint,{unsafe_var,'R',{'try',3}}},
{7,erl_lint,{unsafe_var,'Rc',{'try',3}}},
- {11,erl_lint,{unsafe_var,'R',{'try',10}}},
{13,erl_lint,{unbound_var,'RR'}},
{13,erl_lint,{unbound_var,'Ro'}},
{13,erl_lint,{unsafe_var,'R',{'try',10}}},
@@ -1225,7 +1224,6 @@ unsafe_vars_try(Config) when is_list(Config) ->
{15,erl_lint,{unsafe_var,'R',{'try',10}}},
{15,erl_lint,{unsafe_var,'RR',{'try',10}}},
{15,erl_lint,{unsafe_var,'Ro',{'try',10}}},
- {19,erl_lint,{unsafe_var,'R',{'try',18}}},
{21,erl_lint,{unbound_var,'RR'}},
{21,erl_lint,{unsafe_var,'R',{'try',18}}},
{23,erl_lint,{unsafe_var,'Class',{'try',18}}},
@@ -1251,8 +1249,7 @@ unsafe_vars_try(Config) when is_list(Config) ->
{X,Try,R,RR,Ro,Rc,Ra,Class,Data}.
">>,
[],
- {errors,[{4,erl_lint,{unsafe_var,'R',{'try',3}}},
- {6,erl_lint,{unbound_var,'RR'}},
+ {errors,[{6,erl_lint,{unbound_var,'RR'}},
{6,erl_lint,{unbound_var,'Ro'}},
{6,erl_lint,{unsafe_var,'R',{'try',3}}},
{8,erl_lint,{unsafe_var,'Class',{'try',3}}},
--
2.26.2