From f846bf70b0c97ce66f29b0ff88a50316924bf34e Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Thu, 6 Jun 2013 01:34:25 +0200 Subject: Fix variable usage tracking in erl_lint When analyzing complex expressions (i.e. comprehensions, cases, tries, ifs and receives), erl_lint does not forget about old unused variables when returning the updated variable table. This causes a bug where old unused variables are not recorded as such: t(X, Y) -> #r{a=[ K || K <- Y ],b=[ K || K <- Y ]}. As erl_lint uses vtmerge_pat/2 to merge the results of the analysis of the two list comprehensions, X is marked as used and the warning is not emitted. The function vtmerge_pat/2 is used instead of the similar vtmerge/2 which does not mark multiple occurrences of a variable as usage to handle cases like the following one: t(X, Y) -> #r{a=A=X,b=A=Y}. Other simpler expressions like conses, tuples and external fun references do not correctly follow this behaviour, e.g. A is not marked as used in the following code: t(X, Y) -> {A=X,A=Y}. This commit fixes both issues and makes erl_lint not return old unused variables in updated tables and makes all compound expressions use vtmerge_pat/2. Reported-by: Anders Ramsell --- lib/stdlib/src/erl_lint.erl | 42 ++++++++++++++++++++++++------------------ 1 file changed, 24 insertions(+), 18 deletions(-) (limited to 'lib/stdlib/src/erl_lint.erl') diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 8f07750b9b..9284f08b30 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -1953,12 +1953,10 @@ expr({string,_Line,_S}, _Vt, St) -> {[],St}; expr({nil,_Line}, _Vt, St) -> {[],St}; expr({cons,_Line,H,T}, Vt, St) -> expr_list([H,T], Vt, St); -expr({lc,_Line,E,Qs}, Vt0, St0) -> - {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), - {vtold(Vt, Vt0),St}; %Don't export local variables -expr({bc,_Line,E,Qs}, Vt0, St0) -> - {Vt,St} = handle_comprehension(E, Qs, Vt0, St0), - {vtold(Vt,Vt0),St}; %Don't export local variables +expr({lc,_Line,E,Qs}, Vt, St) -> + handle_comprehension(E, Qs, Vt, St); +expr({bc,_Line,E,Qs}, Vt, St) -> + handle_comprehension(E, Qs, Vt, St); expr({tuple,_Line,Es}, Vt, St) -> expr_list(Es, Vt, St); expr({record_index,Line,Name,Field}, _Vt, St) -> @@ -2012,8 +2010,7 @@ expr({'fun',Line,Body}, Vt, St) -> %%No one can think funs export! case Body of {clauses,Cs} -> - {Bvt, St1} = fun_clauses(Cs, Vt, St), - {vtupdate(Bvt, Vt), St1}; + fun_clauses(Cs, Vt, St); {function,F,A} -> %% BifClash - Fun expression %% N.B. Only allows BIFs here as well, NO IMPORTS!! @@ -2111,12 +2108,12 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> {Evt0,St1} = exprs(Es, Vt, St0), TryLine = {'try',Line}, Uvt = vtunsafe(vtnames(vtnew(Evt0, Vt)), TryLine, []), - Evt1 = vtupdate(Uvt, vtupdate(Evt0, Vt)), - {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, Evt1, St1), + Evt1 = vtupdate(Uvt, Evt0), + {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, vtupdate(Evt1, Vt), St1), Rvt0 = Sccs, Rvt1 = vtupdate(vtunsafe(vtnames(vtnew(Rvt0, Vt)), TryLine, []), Rvt0), Evt2 = vtmerge(Evt1, Rvt1), - {Avt0,St} = exprs(As, Evt2, St2), + {Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2), Avt1 = vtupdate(vtunsafe(vtnames(vtnew(Avt0, Vt)), TryLine, []), Avt0), Avt = vtmerge(Evt2, Avt1), {Avt,St}; @@ -2150,10 +2147,11 @@ expr({remote,Line,_M,_F}, _Vt, St) -> %% {UsedVarTable,State} expr_list(Es, Vt, St) -> - foldl(fun (E, {Esvt,St0}) -> - {Evt,St1} = expr(E, Vt, St0), - {vtmerge(Evt, Esvt),St1} - end, {[],St}, Es). + {Vt1,St1} = foldl(fun (E, {Esvt,St0}) -> + {Evt,St1} = expr(E, Vt, St0), + {vtmerge_pat(Evt, Esvt),St1} + end, {[],St}, Es), + {vtmerge(vtnew(Vt1, Vt), vtold(Vt1, Vt)),St1}. record_expr(Line, Rec, Vt, St0) -> St1 = warn_invalid_record(Line, Rec, St0), @@ -2843,7 +2841,9 @@ icrt_export(Csvt, Vt, In, St) -> Uvt = vtmerge(Evt, Unused), %% Make exported and unsafe unused variables unused in subsequent code: Vt2 = vtmerge(Uvt, vtsubtract(Vt1, Uvt)), - {Vt2,St}. + %% Forget about old variables which were not used: + Vt3 = vtmerge(vtnew(Vt2, Vt), vt_no_unused(vtold(Vt2, Vt))), + {Vt3,St}. handle_comprehension(E, Qs, Vt0, St0) -> {Vt1, Uvt, St1} = lc_quals(Qs, Vt0, St0), @@ -2856,7 +2856,11 @@ handle_comprehension(E, Qs, Vt0, St0) -> %% Local variables that have not been shadowed. {_,St} = check_unused_vars(Vt2, Vt0, St4), Vt3 = vtmerge(vtsubtract(Vt2, Uvt), Uvt), - {Vt3,St}. + %% Don't export local variables. + Vt4 = vtold(Vt3, Vt0), + %% Forget about old variables which were not used. + Vt5 = vt_no_unused(Vt4), + {Vt5,St}. %% lc_quals(Qualifiers, ImportVarTable, State) -> %% {VarTable,ShadowedVarTable,State} @@ -2920,7 +2924,7 @@ fun_clauses(Cs, Vt, St) -> {Cvt,St1} = fun_clause(C, Vt, St0), {vtmerge(Cvt, Bvt0),St1} end, {[],St#lint{recdef_top = false}}, Cs), - {Bvt,St2#lint{recdef_top = OldRecDef}}. + {vt_no_unused(vtold(Bvt, Vt)),St2#lint{recdef_top = OldRecDef}}. fun_clause({clause,_Line,H,G,B}, Vt0, St0) -> {Hvt,Binvt,St1} = head(H, Vt0, [], St0), % No imported pattern variables @@ -3181,6 +3185,8 @@ vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt, _ -> true end]. +vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused]. + %% vunion(VarTable1, VarTable2) -> [VarName]. %% vunion([VarTable]) -> [VarName]. %% vintersection(VarTable1, VarTable2) -> [VarName]. -- cgit v1.2.3 From 9ce148b1059e4da746a11f1d80a653340216c468 Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Mon, 22 Jul 2013 21:41:31 +0200 Subject: Fix unsafe variable tracking in try expressions Variables used in the body of a try expression were marked as unsafe *and* used, which makes no sense as an unsafe variable can't be used. Function vtsubtract/2 is used to forget usage of such unsafe variables. Reported-by: Paul Davis --- lib/stdlib/src/erl_lint.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'lib/stdlib/src/erl_lint.erl') diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 9284f08b30..708ef44fed 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2108,7 +2108,7 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> {Evt0,St1} = exprs(Es, Vt, St0), TryLine = {'try',Line}, Uvt = vtunsafe(vtnames(vtnew(Evt0, Vt)), TryLine, []), - Evt1 = vtupdate(Uvt, Evt0), + Evt1 = vtupdate(Uvt, vtsubtract(Evt0, Uvt)), {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, vtupdate(Evt1, Vt), St1), Rvt0 = Sccs, Rvt1 = vtupdate(vtunsafe(vtnames(vtnew(Rvt0, Vt)), TryLine, []), Rvt0), -- cgit v1.2.3 From 92460f4035e369be8726c88a72055d0fd6c7cdfe Mon Sep 17 00:00:00 2001 From: Anthony Ramine Date: Wed, 31 Jul 2013 10:31:51 +0200 Subject: Fix variable usage tracking in some record errors When reporting a field redefinition in a record, erl_lint can forget about some old unused variables. f() -> X = 1, #r{a=foo,a=bar,a=qux}. --- lib/stdlib/src/erl_lint.erl | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'lib/stdlib/src/erl_lint.erl') diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 708ef44fed..f599881c07 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2308,7 +2308,7 @@ check_fields(Fs, Name, Fields, Vt, St0, CheckFun) -> check_field({record_field,Lf,{atom,La,F},Val}, Name, Fields, Vt, St, Sfs, CheckFun) -> case member(F, Sfs) of - true -> {Sfs,{Vt,add_error(Lf, {redefine_field,Name,F}, St)}}; + true -> {Sfs,{[],add_error(Lf, {redefine_field,Name,F}, St)}}; false -> {[F|Sfs], case find_field(F, Fields) of -- cgit v1.2.3