aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_lint.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/erl_lint.erl')
-rw-r--r--lib/stdlib/src/erl_lint.erl661
1 files changed, 329 insertions, 332 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 39cc03cf7a..26d8454731 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -130,6 +130,8 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
:: dict:dict(mfa(), line()),
callbacks = dict:new() %Callback types
:: dict:dict(mfa(), line()),
+ optional_callbacks = dict:new() %Optional callbacks
+ :: dict:dict(mfa(), line()),
types = dict:new() %Type definitions
:: dict:dict(ta(), #typeinfo{}),
exp_types=gb_sets:empty() %Exported types
@@ -237,10 +239,7 @@ format_error({too_many_arguments,Arity}) ->
"maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
%% --- patterns and guards ---
format_error(illegal_pattern) -> "illegal pattern";
-format_error(illegal_map_key) ->
- "illegal map key";
-format_error({illegal_map_key_variable,K}) ->
- io_lib:format("illegal use of variable ~w in map",[K]);
+format_error(illegal_map_key) -> "illegal map key in pattern";
format_error(illegal_bin_pattern) ->
"binary patterns cannot be matched in parallel using '='";
format_error(illegal_expr) -> "illegal expression";
@@ -313,13 +312,20 @@ format_error({undefined_behaviour,Behaviour}) ->
io_lib:format("behaviour ~w undefined", [Behaviour]);
format_error({undefined_behaviour_callbacks,Behaviour}) ->
io_lib:format("behaviour ~w callback functions are undefined",
- [Behaviour]);
+ [Behaviour]);
format_error({ill_defined_behaviour_callbacks,Behaviour}) ->
io_lib:format("behaviour ~w callback functions erroneously defined",
[Behaviour]);
+format_error({ill_defined_optional_callbacks,Behaviour}) ->
+ io_lib:format("behaviour ~w optional callback functions erroneously defined",
+ [Behaviour]);
format_error({behaviour_info, {_M,F,A}}) ->
io_lib:format("cannot define callback attibute for ~w/~w when "
"behaviour_info is defined",[F,A]);
+format_error({redefine_optional_callback, {F, A}}) ->
+ io_lib:format("optional callback ~w/~w duplicated", [F, A]);
+format_error({undefined_callback, {_M, F, A}}) ->
+ io_lib:format("callback ~w/~w is undefined", [F, A]);
%% --- types and specs ---
format_error({singleton_typevar, Name}) ->
io_lib:format("type variable ~w is only used once (is unbound)", [Name]);
@@ -331,14 +337,10 @@ format_error({undefined_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s undefined", [TypeName, gen_type_paren(Arity)]);
format_error({unused_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is unused", [TypeName, gen_type_paren(Arity)]);
-%% format_error({new_builtin_type, {TypeName, Arity}}) ->
-%% io_lib:format("type ~w~s is a new builtin type; "
-%% "its (re)definition is allowed only until the next release",
-%% [TypeName, gen_type_paren(Arity)]);
-format_error({new_var_arity_type, TypeName}) ->
- io_lib:format("type ~w is a new builtin type; "
+format_error({new_builtin_type, {TypeName, Arity}}) ->
+ io_lib:format("type ~w~s is a new builtin type; "
"its (re)definition is allowed only until the next release",
- [TypeName]);
+ [TypeName, gen_type_paren(Arity)]);
format_error({builtin_type, {TypeName, Arity}}) ->
io_lib:format("type ~w~s is a builtin type; it cannot be redefined",
[TypeName, gen_type_paren(Arity)]);
@@ -352,10 +354,14 @@ format_error({type_syntax, Constr}) ->
io_lib:format("bad ~w type", [Constr]);
format_error({redefine_spec, {M, F, A}}) ->
io_lib:format("spec for ~w:~w/~w already defined", [M, F, A]);
-format_error({redefine_callback, {M, F, A}}) ->
- io_lib:format("callback ~w:~w/~w already defined", [M, F, A]);
-format_error({spec_fun_undefined, {M, F, A}}) ->
- io_lib:format("spec for undefined function ~w:~w/~w", [M, F, A]);
+format_error({redefine_spec, {F, A}}) ->
+ io_lib:format("spec for ~w/~w already defined", [F, A]);
+format_error({redefine_callback, {F, A}}) ->
+ io_lib:format("callback ~w/~w already defined", [F, A]);
+format_error({bad_callback, {M, F, A}}) ->
+ io_lib:format("explicit module not allowed for callback ~w:~w/~w ", [M, F, A]);
+format_error({spec_fun_undefined, {F, A}}) ->
+ io_lib:format("spec for undefined function ~w/~w", [F, A]);
format_error({missing_spec, {F,A}}) ->
io_lib:format("missing specification for function ~w/~w", [F, A]);
format_error(spec_wrong_arity) ->
@@ -383,9 +389,7 @@ format_error({underspecified_opaque, {TypeName, Arity}}) ->
[TypeName, gen_type_paren(Arity)]);
%% --- obsolete? unused? ---
format_error({format_error, {Fmt, Args}}) ->
- io_lib:format(Fmt, Args);
-format_error({mnemosyne, What}) ->
- "mnemosyne " ++ What ++ ", missing transformation".
+ io_lib:format(Fmt, Args).
gen_type_paren(Arity) when is_integer(Arity), Arity >= 0 ->
gen_type_paren_1(Arity, ")").
@@ -727,6 +731,8 @@ attribute_state({attribute,L,spec,{Fun,Types}}, St) ->
spec_decl(L, Fun, Types, St);
attribute_state({attribute,L,callback,{Fun,Types}}, St) ->
callback_decl(L, Fun, Types, St);
+attribute_state({attribute,L,optional_callbacks,Es}, St) ->
+ optional_callbacks(L, Es, St);
attribute_state({attribute,L,on_load,Val}, St) ->
on_load(L, Val, St);
attribute_state({attribute,_L,_Other,_Val}, St) -> % Ignore others
@@ -751,8 +757,6 @@ function_state({attribute,La,Attr,_Val}, St) ->
add_error(La, {attribute,Attr}, St);
function_state({function,L,N,A,Cs}, St) ->
function(L, N, A, Cs, St);
-function_state({rule,L,_N,_A,_Cs}, St) ->
- add_error(L, {mnemosyne,"rule"}, St);
function_state({eof,L}, St) -> eof(L, St).
%% eof(LastLine, State) ->
@@ -834,57 +838,73 @@ check_behaviour(St0) ->
%% Check behaviours for existence and defined functions.
behaviour_check(Bs, St0) ->
- {AllBfs,St1} = all_behaviour_callbacks(Bs, [], St0),
- St = behaviour_missing_callbacks(AllBfs, St1),
+ {AllBfs0, St1} = all_behaviour_callbacks(Bs, [], St0),
+ St = behaviour_missing_callbacks(AllBfs0, St1),
+ Exports = exports(St0),
+ F = fun(Bfs, OBfs) ->
+ [B || B <- Bfs,
+ not lists:member(B, OBfs)
+ orelse gb_sets:is_member(B, Exports)]
+ end,
+ %% After fixing missing callbacks new warnings may be emitted.
+ AllBfs = [{Item,F(Bfs0, OBfs0)} || {Item,Bfs0,OBfs0} <- AllBfs0],
behaviour_conflicting(AllBfs, St).
all_behaviour_callbacks([{Line,B}|Bs], Acc, St0) ->
- {Bfs0,St} = behaviour_callbacks(Line, B, St0),
- all_behaviour_callbacks(Bs, [{{Line,B},Bfs0}|Acc], St);
+ {Bfs0,OBfs0,St} = behaviour_callbacks(Line, B, St0),
+ all_behaviour_callbacks(Bs, [{{Line,B},Bfs0,OBfs0}|Acc], St);
all_behaviour_callbacks([], Acc, St) -> {reverse(Acc),St}.
behaviour_callbacks(Line, B, St0) ->
try B:behaviour_info(callbacks) of
- Funcs when is_list(Funcs) ->
- All = all(fun({FuncName, Arity}) ->
- is_atom(FuncName) andalso is_integer(Arity);
- ({FuncName, Arity, Spec}) ->
- is_atom(FuncName) andalso is_integer(Arity)
- andalso is_list(Spec);
- (_Other) ->
- false
- end,
- Funcs),
- MaybeRemoveSpec = fun({_F,_A}=FA) -> FA;
- ({F,A,_S}) -> {F,A};
- (Other) -> Other
- end,
- if
- All =:= true ->
- {[MaybeRemoveSpec(F) || F <- Funcs], St0};
+ undefined ->
+ St1 = add_warning(Line, {undefined_behaviour_callbacks, B}, St0),
+ {[], [], St1};
+ Funcs ->
+ case is_fa_list(Funcs) of
true ->
+ try B:behaviour_info(optional_callbacks) of
+ undefined ->
+ {Funcs, [], St0};
+ OptFuncs ->
+ %% OptFuncs should always be OK thanks to
+ %% sys_pre_expand.
+ case is_fa_list(OptFuncs) of
+ true ->
+ {Funcs, OptFuncs, St0};
+ false ->
+ W = {ill_defined_optional_callbacks, B},
+ St1 = add_warning(Line, W, St0),
+ {Funcs, [], St1}
+ end
+ catch
+ _:_ ->
+ {Funcs, [], St0}
+ end;
+ false ->
St1 = add_warning(Line,
- {ill_defined_behaviour_callbacks,B},
+ {ill_defined_behaviour_callbacks, B},
St0),
- {[], St1}
- end;
- undefined ->
- St1 = add_warning(Line, {undefined_behaviour_callbacks,B}, St0),
- {[], St1};
- _Other ->
- St1 = add_warning(Line, {ill_defined_behaviour_callbacks,B}, St0),
- {[], St1}
+ {[], [], St1}
+ end
catch
_:_ ->
- St1 = add_warning(Line, {undefined_behaviour,B}, St0),
- {[], St1}
+ St1 = add_warning(Line, {undefined_behaviour, B}, St0),
+ {[], [], St1}
end.
-behaviour_missing_callbacks([{{Line,B},Bfs}|T], St0) ->
+behaviour_missing_callbacks([{{Line,B},Bfs0,OBfs}|T], St0) ->
+ Bfs = ordsets:subtract(ordsets:from_list(Bfs0), ordsets:from_list(OBfs)),
Exports = gb_sets:to_list(exports(St0)),
- Missing = ordsets:subtract(ordsets:from_list(Bfs), Exports),
+ Missing = ordsets:subtract(Bfs, Exports),
St = foldl(fun (F, S0) ->
- add_warning(Line, {undefined_behaviour_func,F,B}, S0)
+ case is_fa(F) of
+ true ->
+ M = {undefined_behaviour_func,F,B},
+ add_warning(Line, M, S0);
+ false ->
+ S0 % ill_defined_behaviour_callbacks
+ end
end, St0, Missing),
behaviour_missing_callbacks(T, St);
behaviour_missing_callbacks([], St) -> St.
@@ -1046,10 +1066,9 @@ check_undefined_types(#lint{usage=Usage,types=Def}=St0) ->
Used = Usage#usage.used_types,
UTAs = dict:fetch_keys(Used),
Undef = [{TA,dict:fetch(TA, Used)} ||
- {T,_}=TA <- UTAs,
+ TA <- UTAs,
not dict:is_key(TA, Def),
- not is_default_type(TA),
- not is_newly_introduced_var_arity_type(T)],
+ not is_default_type(TA)],
foldl(fun ({TA,L}, St) ->
add_error(L, {undefined_type,TA}, St)
end, St0, Undef).
@@ -1127,19 +1146,29 @@ check_unused_records(Forms, St0) ->
end.
check_callback_information(#lint{callbacks = Callbacks,
- defined = Defined} = State) ->
- case gb_sets:is_member({behaviour_info,1}, Defined) of
- false -> State;
+ optional_callbacks = OptionalCbs,
+ defined = Defined} = St0) ->
+ OptFun = fun({MFA, Line}, St) ->
+ case dict:is_key(MFA, Callbacks) of
+ true ->
+ St;
+ false ->
+ add_error(Line, {undefined_callback, MFA}, St)
+ end
+ end,
+ St1 = lists:foldl(OptFun, St0, dict:to_list(OptionalCbs)),
+ case gb_sets:is_member({behaviour_info, 1}, Defined) of
+ false -> St1;
true ->
case dict:size(Callbacks) of
- 0 -> State;
+ 0 -> St1;
_ ->
CallbacksList = dict:to_list(Callbacks),
FoldL =
- fun({Fa,Line},St) ->
+ fun({Fa, Line}, St) ->
add_error(Line, {behaviour_info, Fa}, St)
end,
- lists:foldl(FoldL, State, CallbacksList)
+ lists:foldl(FoldL, St1, CallbacksList)
end
end.
@@ -1404,20 +1433,7 @@ pattern({cons,_Line,H,T}, Vt, Old, Bvt, St0) ->
pattern({tuple,_Line,Ps}, Vt, Old, Bvt, St) ->
pattern_list(Ps, Vt, Old, Bvt, St);
pattern({map,_Line,Ps}, Vt, Old, Bvt, St) ->
- foldl(fun
- ({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
- {Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
- ({map_field_exact,L,KP,VP}, {Psvt,Bvt0,St0}) ->
- case is_valid_map_key(KP, pattern, St0) of
- true ->
- {Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0),
- {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1), St1};
- false ->
- {Psvt,Bvt0,add_error(L, illegal_map_key, St0)};
- {false,variable,Var} ->
- {Psvt,Bvt0,add_error(L, {illegal_map_key_variable,Var}, St0)}
- end
- end, {[],[],St}, Ps);
+ pattern_map(Ps, Vt, Old, Bvt, St);
%%pattern({struct,_Line,_Tag,Ps}, Vt, Old, Bvt, St) ->
%% pattern_list(Ps, Vt, Old, Bvt, St);
pattern({record_index,Line,Name,Field}, _Vt, _Old, _Bvt, St) ->
@@ -1571,6 +1587,21 @@ is_pattern_expr_1({op,_Line,Op,A1,A2}) ->
erl_internal:arith_op(Op, 2) andalso all(fun is_pattern_expr/1, [A1,A2]);
is_pattern_expr_1(_Other) -> false.
+pattern_map(Ps, Vt, Old, Bvt, St) ->
+ foldl(fun
+ ({map_field_assoc,L,_,_}, {Psvt,Bvt0,St0}) ->
+ {Psvt,Bvt0,add_error(L, illegal_pattern, St0)};
+ ({map_field_exact,L,K,V}, {Psvt,Bvt0,St0}) ->
+ case is_valid_map_key(K) of
+ true ->
+ {Kvt,St1} = expr(K, Vt, St0),
+ {Vvt,Bvt2,St2} = pattern(V, Vt, Old, Bvt, St1),
+ {vtmerge_pat(vtmerge_pat(Kvt, Vvt), Psvt), vtmerge_pat(Bvt0, Bvt2), St2};
+ false ->
+ {Psvt,Bvt0,add_error(L, illegal_map_key, St0)}
+ end
+ end, {[],[],St}, Ps).
+
%% pattern_bin([Element], VarTable, Old, BinVarTable, State) ->
%% {UpdVarTable,UpdBinVarTable,State}.
%% Check a pattern group. BinVarTable are used binsize variables.
@@ -2085,8 +2116,8 @@ expr({'receive',Line,Cs,To,ToEs}, Vt, St0) ->
{Cvt,St3} = icrt_clauses(Cs, Vt, St2),
%% Csvts = [vtnew(Tevt, Vt)|Cvt], %This is just NEW variables!
Csvts = [Tevt|Cvt],
- {Rvt,St4} = icrt_export(Csvts, Vt, {'receive',Line}, St3),
- {vtmerge([Tvt,Tevt,Rvt]),St4};
+ Rvt = icrt_export(Csvts, Vt, {'receive',Line}),
+ {vtmerge([Tvt,Tevt,Rvt]),St3};
expr({'fun',Line,Body}, Vt, St) ->
%%No one can think funs export!
case Body of
@@ -2197,21 +2228,20 @@ expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) ->
%% passes cannot handle exports in combination with 'after'.
{Evt0,St1} = exprs(Es, Vt, St0),
TryLine = {'try',Line},
- Uvt = vtunsafe(vtnames(vtnew(Evt0, Vt)), TryLine, []),
- Evt1 = vtupdate(Uvt, vtsubtract(Evt0, Uvt)),
+ Uvt = vtunsafe(TryLine, Evt0, Vt),
+ 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),
+ Rvt1 = vtupdate(vtunsafe(TryLine, Rvt0, Vt), Rvt0),
Evt2 = vtmerge(Evt1, Rvt1),
{Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2),
- Avt1 = vtupdate(vtunsafe(vtnames(vtnew(Avt0, Vt)), TryLine, []), Avt0),
+ Avt1 = vtupdate(vtunsafe(TryLine, Avt0, Vt), Avt0),
Avt = vtmerge(Evt2, Avt1),
{Avt,St};
expr({'catch',Line,E}, Vt, St0) ->
%% No new variables added, flag new variables as unsafe.
- {Evt,St1} = expr(E, Vt, St0),
- Uvt = vtunsafe(vtnames(vtnew(Evt, Vt)), {'catch',Line}, []),
- {vtupdate(Uvt,vtupdate(Evt, Vt)),St1};
+ {Evt,St} = expr(E, Vt, St0),
+ {vtupdate(vtunsafe({'catch',Line}, Evt, Vt), Evt),St};
expr({match,_Line,P,E}, Vt, St0) ->
{Evt,St1} = expr(E, Vt, St0),
{Pvt,Bvt,St2} = pattern(P, vtupdate(Evt, Vt), St1),
@@ -2224,9 +2254,8 @@ expr({op,Line,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
{Evt1,St1} = expr(L, Vt, St0),
Vt1 = vtupdate(Evt1, Vt),
{Evt2,St2} = expr(R, Vt1, St1),
- Vt2 = vtmerge(Evt2, Vt1),
- {Vt3,St3} = icrt_export([Vt1,Vt2], Vt1, {Op,Line}, St2),
- {vtmerge(Evt1, Vt3),St3};
+ Evt3 = vtupdate(vtunsafe({Op,Line}, Evt2, Vt1), Evt2),
+ {vtmerge(Evt1, Evt3),St2};
expr({op,_Line,_Op,L,R}, Vt, St) ->
expr_list([L,R], Vt, St); %They see the same variables
%% The following are not allowed to occur anywhere!
@@ -2254,14 +2283,9 @@ check_assoc_fields([{map_field_assoc,_,_,_}|Fs], St) ->
check_assoc_fields([], St) ->
St.
-map_fields([{Tag,Line,K,V}|Fs], Vt, St, F) when Tag =:= map_field_assoc;
- Tag =:= map_field_exact ->
- St1 = case is_valid_map_key(K, St) of
- true -> St;
- false -> add_error(Line, illegal_map_key, St);
- {false,variable,Var} -> add_error(Line, {illegal_map_key_variable,Var}, St)
- end,
- {Pvt,St2} = F([K,V], Vt, St1),
+map_fields([{Tag,_,K,V}|Fs], Vt, St, F) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ {Pvt,St2} = F([K,V], Vt, St),
{Vts,St3} = map_fields(Fs, Vt, St2, F),
{vtupdate(Pvt, Vts),St3};
map_fields([], Vt, St, _) ->
@@ -2319,21 +2343,14 @@ is_valid_call(Call) ->
_ -> true
end.
-%% is_valid_map_key(K,St) -> true | false | {false, Var::atom()}
-%% check for value expression without variables
-
-is_valid_map_key(K,St) ->
- is_valid_map_key(K,expr,St).
-is_valid_map_key(K,Ctx,St) ->
- case expr(K,[],St) of
- {[],_} ->
- is_valid_map_key_value(K,Ctx);
- {[Var|_],_} ->
- {false,variable,element(1,Var)}
- end.
+%% is_valid_map_key(K,St) -> true | false
+%% variables are allowed for patterns only at the top of the tree
-is_valid_map_key_value(K,Ctx) ->
+is_valid_map_key({var,_,_}) -> true;
+is_valid_map_key(K) -> is_valid_map_key_value(K).
+is_valid_map_key_value(K) ->
case K of
+ {var,_,_} -> false;
{char,_,_} -> true;
{integer,_,_} -> true;
{float,_,_} -> true;
@@ -2341,36 +2358,36 @@ is_valid_map_key_value(K,Ctx) ->
{nil,_} -> true;
{atom,_,_} -> true;
{cons,_,H,T} ->
- is_valid_map_key_value(H,Ctx) andalso
- is_valid_map_key_value(T,Ctx);
+ is_valid_map_key_value(H) andalso
+ is_valid_map_key_value(T);
{tuple,_,Es} ->
foldl(fun(E,B) ->
- B andalso is_valid_map_key_value(E,Ctx)
+ B andalso is_valid_map_key_value(E)
end,true,Es);
{map,_,Arg,Ps} ->
% only check for value expressions to be valid
% invalid map expressions are later checked in
% core and kernel
- is_valid_map_key_value(Arg,Ctx) andalso foldl(fun
+ is_valid_map_key_value(Arg) andalso foldl(fun
({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
- Tag =:= map_field_exact, Ctx =:= expr ->
- B andalso is_valid_map_key_value(Ke,Ctx)
- andalso is_valid_map_key_value(Ve,Ctx);
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve);
(_,_) -> false
end,true,Ps);
{map,_,Ps} ->
foldl(fun
({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
- Tag =:= map_field_exact, Ctx =:= expr ->
- B andalso is_valid_map_key_value(Ke,Ctx)
- andalso is_valid_map_key_value(Ve,Ctx);
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve);
(_,_) -> false
end, true, Ps);
{record,_,_,Fs} ->
foldl(fun
({record_field,_,Ke,Ve},B) ->
- B andalso is_valid_map_key_value(Ke,Ctx)
- andalso is_valid_map_key_value(Ve,Ctx)
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
end,true,Fs);
{bin,_,Es} ->
% only check for value expressions to be valid
@@ -2378,9 +2395,9 @@ is_valid_map_key_value(K,Ctx) ->
% core and kernel
foldl(fun
({bin_element,_,E,_,_},B) ->
- B andalso is_valid_map_key_value(E,Ctx)
+ B andalso is_valid_map_key_value(E)
end,true,Es);
- _ -> false
+ Val -> is_pattern_expr(Val)
end.
%% record_def(Line, RecordName, [RecField], State) -> State.
@@ -2615,30 +2632,21 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
true ->
case is_obsolete_builtin_type(TypePair) of
true -> StoreType(St0);
- false -> add_error(Line, {builtin_type, TypePair}, St0)
-%% case is_newly_introduced_builtin_type(TypePair) of
-%% %% allow some types just for bootstrapping
-%% true ->
-%% Warn = {new_builtin_type, TypePair},
-%% St1 = add_warning(Line, Warn, St0),
-%% StoreType(St1);
-%% false ->
-%% add_error(Line, {builtin_type, TypePair}, St0)
-%% end
+ false ->
+ case is_newly_introduced_builtin_type(TypePair) of
+ %% allow some types just for bootstrapping
+ true ->
+ Warn = {new_builtin_type, TypePair},
+ St1 = add_warning(Line, Warn, St0),
+ StoreType(St1);
+ false ->
+ add_error(Line, {builtin_type, TypePair}, St0)
+ end
end;
false ->
- case
- dict:is_key(TypePair, TypeDefs) orelse
- is_var_arity_type(TypeName)
- of
+ case dict:is_key(TypePair, TypeDefs) of
true ->
- case is_newly_introduced_var_arity_type(TypeName) of
- true ->
- Warn = {new_var_arity_type, TypeName},
- add_warning(Line, Warn, St0);
- false ->
- add_error(Line, {redefine_type, TypePair}, St0)
- end;
+ add_error(Line, {redefine_type, TypePair}, St0);
false ->
St1 = case
Attr =:= opaque andalso
@@ -2675,7 +2683,7 @@ check_type({paren_type, _L, [Type]}, SeenVars, St) ->
check_type({remote_type, L, [{atom, _, Mod}, {atom, _, Name}, Args]},
SeenVars, #lint{module=CurrentMod} = St) ->
case Mod =:= CurrentMod of
- true -> check_type({type, L, Name, Args}, SeenVars, St);
+ true -> check_type({user_type, L, Name, Args}, SeenVars, St);
false ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
@@ -2709,12 +2717,15 @@ check_type({type, L, range, [From, To]}, SeenVars, St) ->
_ -> add_error(L, {type_syntax, range}, St)
end,
{SeenVars, St1};
-check_type({type, _L, map, any}, SeenVars, St) -> {SeenVars, St};
+check_type({type, L, map, any}, SeenVars, St) ->
+ %% To get usage right while map/0 is a newly_introduced_builtin_type.
+ St1 = used_type({map, 0}, L, St),
+ {SeenVars, St1};
check_type({type, _L, map, Pairs}, SeenVars, St) ->
lists:foldl(fun(Pair, {AccSeenVars, AccSt}) ->
check_type(Pair, AccSeenVars, AccSt)
end, {SeenVars, St}, Pairs);
-check_type({type, _L, map_field_assoc, Dom, Range}, SeenVars, St) ->
+check_type({type, _L, map_field_assoc, [Dom, Range]}, SeenVars, St) ->
check_type({type, -1, product, [Dom, Range]}, SeenVars, St);
check_type({type, _L, tuple, any}, SeenVars, St) -> {SeenVars, St};
check_type({type, _L, any}, SeenVars, St) -> {SeenVars, St};
@@ -2733,41 +2744,39 @@ check_type({type, L, record, [Name|Fields]}, SeenVars, St) ->
check_record_types(L, Atom, Fields, SeenVars, St1);
_ -> {SeenVars, add_error(L, {type_syntax, record}, St)}
end;
-check_type({type, _L, product, Args}, SeenVars, St) ->
+check_type({type, _L, Tag, Args}, SeenVars, St) when Tag =:= product;
+ Tag =:= union;
+ Tag =:= tuple ->
lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
check_type(T, AccSeenVars, AccSt)
end, {SeenVars, St}, Args);
check_type({type, La, TypeName, Args}, SeenVars, St) ->
- #lint{usage=Usage, module = Module, types=Types} = St,
+ #lint{module = Module, types=Types} = St,
Arity = length(Args),
TypePair = {TypeName, Arity},
- St1 = case is_var_arity_type(TypeName) of
- true -> St;
- false ->
- Obsolete = (is_warn_enabled(deprecated_type, St)
- andalso obsolete_builtin_type(TypePair)),
- IsObsolete =
- case Obsolete of
- {deprecated, Repl, _} when element(1, Repl) =/= Module ->
- case dict:find(TypePair, Types) of
- {ok, _} -> false;
- error -> true
- end;
- _ -> false
- end,
- case IsObsolete of
- true ->
+ Obsolete = (is_warn_enabled(deprecated_type, St)
+ andalso obsolete_builtin_type(TypePair)),
+ St1 = case Obsolete of
+ {deprecated, Repl, _} when element(1, Repl) =/= Module ->
+ case dict:find(TypePair, Types) of
+ {ok, _} ->
+ used_type(TypePair, La, St);
+ error ->
{deprecated, Replacement, Rel} = Obsolete,
Tag = deprecated_builtin_type,
W = {Tag, TypePair, Replacement, Rel},
- add_warning(La, W, St);
- false ->
- OldUsed = Usage#usage.used_types,
- UsedTypes = dict:store(TypePair, La, OldUsed),
- St#lint{usage=Usage#usage{used_types=UsedTypes}}
- end
- end,
+ add_warning(La, W, St)
+ end;
+ _ -> St
+ end,
check_type({type, -1, product, Args}, SeenVars, St1);
+check_type({user_type, L, TypeName, Args}, SeenVars, St) ->
+ Arity = length(Args),
+ TypePair = {TypeName, Arity},
+ St1 = used_type(TypePair, L, St),
+ lists:foldl(fun(T, {AccSeenVars, AccSt}) ->
+ check_type(T, AccSeenVars, AccSt)
+ end, {SeenVars, St1}, Args);
check_type(I, SeenVars, St) ->
case erl_eval:partial_eval(I) of
{integer,_ILn,_Integer} -> {SeenVars, St};
@@ -2809,95 +2818,24 @@ check_record_types([{type, _, field_type, [{atom, AL, FName}, Type]}|Left],
check_record_types([], _Name, _DefFields, SeenVars, St, _SeenFields) ->
{SeenVars, St}.
-is_var_arity_type(tuple) -> true;
-is_var_arity_type(map) -> true;
-is_var_arity_type(product) -> true;
-is_var_arity_type(union) -> true;
-is_var_arity_type(record) -> true;
-is_var_arity_type(_) -> false.
-
-is_default_type({any, 0}) -> true;
-is_default_type({arity, 0}) -> true;
-is_default_type({array, 0}) -> true;
-is_default_type({atom, 0}) -> true;
-is_default_type({atom, 1}) -> true;
-is_default_type({binary, 0}) -> true;
-is_default_type({binary, 2}) -> true;
-is_default_type({bitstring, 0}) -> true;
-is_default_type({bool, 0}) -> true;
-is_default_type({boolean, 0}) -> true;
-is_default_type({byte, 0}) -> true;
-is_default_type({char, 0}) -> true;
-is_default_type({dict, 0}) -> true;
-is_default_type({digraph, 0}) -> true;
-is_default_type({float, 0}) -> true;
-is_default_type({'fun', 0}) -> true;
-is_default_type({'fun', 2}) -> true;
-is_default_type({function, 0}) -> true;
-is_default_type({gb_set, 0}) -> true;
-is_default_type({gb_tree, 0}) -> true;
-is_default_type({identifier, 0}) -> true;
-is_default_type({integer, 0}) -> true;
-is_default_type({integer, 1}) -> true;
-is_default_type({iodata, 0}) -> true;
-is_default_type({iolist, 0}) -> true;
-is_default_type({list, 0}) -> true;
-is_default_type({list, 1}) -> true;
-is_default_type({maybe_improper_list, 0}) -> true;
-is_default_type({maybe_improper_list, 2}) -> true;
-is_default_type({mfa, 0}) -> true;
-is_default_type({module, 0}) -> true;
-is_default_type({neg_integer, 0}) -> true;
-is_default_type({nil, 0}) -> true;
-is_default_type({no_return, 0}) -> true;
-is_default_type({node, 0}) -> true;
-is_default_type({non_neg_integer, 0}) -> true;
-is_default_type({none, 0}) -> true;
-is_default_type({nonempty_list, 0}) -> true;
-is_default_type({nonempty_list, 1}) -> true;
-is_default_type({nonempty_improper_list, 2}) -> true;
-is_default_type({nonempty_maybe_improper_list, 0}) -> true;
-is_default_type({nonempty_maybe_improper_list, 2}) -> true;
-is_default_type({nonempty_string, 0}) -> true;
-is_default_type({number, 0}) -> true;
-is_default_type({pid, 0}) -> true;
-is_default_type({port, 0}) -> true;
-is_default_type({pos_integer, 0}) -> true;
-is_default_type({queue, 0}) -> true;
-is_default_type({range, 2}) -> true;
-is_default_type({reference, 0}) -> true;
-is_default_type({set, 0}) -> true;
-is_default_type({string, 0}) -> true;
-is_default_type({term, 0}) -> true;
-is_default_type({timeout, 0}) -> true;
-is_default_type({var, 1}) -> true;
-is_default_type(_) -> false.
-
-is_newly_introduced_var_arity_type(map) -> true;
-is_newly_introduced_var_arity_type(_) -> false.
-
-%% is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
+used_type(TypePair, L, St) ->
+ Usage = St#lint.usage,
+ OldUsed = Usage#usage.used_types,
+ UsedTypes = dict:store(TypePair, L, OldUsed),
+ St#lint{usage=Usage#usage{used_types=UsedTypes}}.
+
+is_default_type({Name, NumberOfTypeVariables}) ->
+ erl_internal:is_type(Name, NumberOfTypeVariables).
+
+is_newly_introduced_builtin_type({map, 0}) -> true;
+is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> false.
is_obsolete_builtin_type(TypePair) ->
obsolete_builtin_type(TypePair) =/= no.
-%% Obsolete in OTP 17.0.
-obsolete_builtin_type({array, 0}) ->
- {deprecated, {array, array, 1}, "OTP 18.0"};
-obsolete_builtin_type({dict, 0}) ->
- {deprecated, {dict, dict, 2}, "OTP 18.0"};
-obsolete_builtin_type({digraph, 0}) ->
- {deprecated, {digraph, graph}, "OTP 18.0"};
-obsolete_builtin_type({gb_set, 0}) ->
- {deprecated, {gb_sets, set, 1}, "OTP 18.0"};
-obsolete_builtin_type({gb_tree, 0}) ->
- {deprecated, {gb_trees, tree, 2}, "OTP 18.0"};
-obsolete_builtin_type({queue, 0}) ->
- {deprecated, {queue, queue, 1}, "OTP 18.0"};
-obsolete_builtin_type({set, 0}) ->
- {deprecated, {sets, set, 1}, "OTP 18.0"};
-obsolete_builtin_type({tid, 0}) ->
- {deprecated, {ets, tid}, "OTP 18.0"};
+%% To keep Dialyzer silent...
+obsolete_builtin_type({1, 255}) ->
+ {deprecated, {2, 255}, ""};
obsolete_builtin_type({Name, A}) when is_atom(Name), is_integer(A) -> no.
%% spec_decl(Line, Fun, Types, State) -> State.
@@ -2909,7 +2847,7 @@ spec_decl(Line, MFA0, TypeSpecs, St0 = #lint{specs = Specs, module = Mod}) ->
end,
St1 = St0#lint{specs = dict:store(MFA, Line, Specs)},
case dict:is_key(MFA, Specs) of
- true -> add_error(Line, {redefine_spec, MFA}, St1);
+ true -> add_error(Line, {redefine_spec, MFA0}, St1);
false -> check_specs(TypeSpecs, Arity, St1)
end.
@@ -2917,16 +2855,50 @@ spec_decl(Line, MFA0, TypeSpecs, St0 = #lint{specs = Specs, module = Mod}) ->
callback_decl(Line, MFA0, TypeSpecs,
St0 = #lint{callbacks = Callbacks, module = Mod}) ->
- MFA = case MFA0 of
- {F, Arity} -> {Mod, F, Arity};
- {_M, _F, Arity} -> MFA0
- end,
- St1 = St0#lint{callbacks = dict:store(MFA, Line, Callbacks)},
- case dict:is_key(MFA, Callbacks) of
- true -> add_error(Line, {redefine_callback, MFA}, St1);
- false -> check_specs(TypeSpecs, Arity, St1)
+ case MFA0 of
+ {_M, _F, _A} -> add_error(Line, {bad_callback, MFA0}, St0);
+ {F, Arity} ->
+ MFA = {Mod, F, Arity},
+ St1 = St0#lint{callbacks = dict:store(MFA, Line, Callbacks)},
+ case dict:is_key(MFA, Callbacks) of
+ true -> add_error(Line, {redefine_callback, MFA0}, St1);
+ false -> check_specs(TypeSpecs, Arity, St1)
+ end
+ end.
+
+%% optional_callbacks(Line, FAs, State) -> State.
+
+optional_callbacks(Line, Term, St0) ->
+ try true = is_fa_list(Term), Term of
+ FAs ->
+ optional_cbs(Line, FAs, St0)
+ catch
+ _:_ ->
+ St0 % ignore others
end.
+optional_cbs(_Line, [], St) ->
+ St;
+optional_cbs(Line, [{F,A}|FAs], St0) ->
+ #lint{optional_callbacks = OptionalCbs, module = Mod} = St0,
+ MFA = {Mod, F, A},
+ St1 = St0#lint{optional_callbacks = dict:store(MFA, Line, OptionalCbs)},
+ St2 = case dict:is_key(MFA, OptionalCbs) of
+ true ->
+ add_error(Line, {redefine_optional_callback, {F,A}}, St1);
+ false ->
+ St1
+ end,
+ optional_cbs(Line, FAs, St2).
+
+is_fa_list([E|L]) -> is_fa(E) andalso is_fa_list(L);
+is_fa_list([]) -> true;
+is_fa_list(_) -> false.
+
+is_fa({FuncName, Arity})
+ when is_atom(FuncName), is_integer(Arity), Arity >= 0 -> true;
+is_fa(_) -> false.
+
check_specs([FunType|Left], Arity, St0) ->
{FunType1, CTypes} =
case FunType of
@@ -2950,10 +2922,11 @@ check_specs([], _Arity, St) ->
St.
check_specs_without_function(#lint{module=Mod,defined=Funcs,specs=Specs}=St) ->
- Fun = fun({M, F, A} = MFA, Line, AccSt) when M =:= Mod ->
- case gb_sets:is_element({F, A}, Funcs) of
+ Fun = fun({M, F, A}, Line, AccSt) when M =:= Mod ->
+ FA = {F, A},
+ case gb_sets:is_element(FA, Funcs) of
true -> AccSt;
- false -> add_error(Line, {spec_fun_undefined, MFA}, AccSt)
+ false -> add_error(Line, {spec_fun_undefined, FA}, AccSt)
end;
({_M, _F, _A}, _Line, AccSt) -> AccSt
end,
@@ -3032,11 +3005,12 @@ check_local_opaque_types(St) ->
dict:fold(FoldFun, St, Ts).
%% icrt_clauses(Clauses, In, ImportVarTable, State) ->
-%% {NewVts,State}.
+%% {UpdVt,State}.
icrt_clauses(Cs, In, Vt, St0) ->
{Csvt,St1} = icrt_clauses(Cs, Vt, St0),
- icrt_export(Csvt, Vt, In, St1).
+ UpdVt = icrt_export(Csvt, Vt, In),
+ {UpdVt,St1}.
%% icrt_clauses(Clauses, ImportVarTable, State) ->
%% {NewVts,State}.
@@ -3046,26 +3020,73 @@ icrt_clauses(Cs, Vt, St) ->
icrt_clause({clause,_Line,H,G,B}, Vt0, St0) ->
{Hvt,Binvt,St1} = head(H, Vt0, St0),
- Vt1 = vtupdate(Hvt, vtupdate(Binvt, Vt0)),
- {Gvt,St2} = guard(G, Vt1, St1),
+ Vt1 = vtupdate(Hvt, Binvt),
+ {Gvt,St2} = guard(G, vtupdate(Vt1, Vt0), St1),
Vt2 = vtupdate(Gvt, Vt1),
- {Bvt,St3} = exprs(B, Vt2, St2),
+ {Bvt,St3} = exprs(B, vtupdate(Vt2, Vt0), St2),
{vtupdate(Bvt, Vt2),St3}.
-icrt_export(Csvt, Vt, In, St) ->
- Vt1 = vtmerge(Csvt),
- All = ordsets:subtract(vintersection(Csvt), vtnames(Vt)),
- Some = ordsets:subtract(vtnames(Vt1), vtnames(Vt)),
- Xvt = vtexport(All, In, []),
- Evt = vtunsafe(ordsets:subtract(Some, All), In, Xvt),
- Unused = vtmerge([unused_vars(Vt0, Vt, St) || Vt0 <- Csvt]),
- %% Exported and unsafe variables may be unused:
- Uvt = vtmerge(Evt, Unused),
- %% Make exported and unsafe unused variables unused in subsequent code:
- Vt2 = vtmerge(Uvt, vtsubtract(Vt1, Uvt)),
- %% Forget about old variables which were not used:
- Vt3 = vtmerge(vtnew(Vt2, Vt), vt_no_unused(vtold(Vt2, Vt))),
- {Vt3,St}.
+icrt_export(Vts, Vt, {Tag,Attrs}) ->
+ {_File,Loc} = loc(Attrs),
+ icrt_export(lists:merge(Vts), Vt, {Tag,Loc}, length(Vts), []).
+
+icrt_export([{V,{{export,_},_,_}}|Vs0], [{V,{{export,_}=S0,_,Ls}}|Vt],
+ In, I, Acc) ->
+ %% V was an exported variable and has been used in an expression in at least
+ %% one clause. Its state needs to be merged from all clauses to silence any
+ %% exported var warning already emitted.
+ {VVs,Vs} = lists:partition(fun ({K,_}) -> K =:= V end, Vs0),
+ S = foldl(fun ({_,{S1,_,_}}, AccS) -> merge_state(AccS, S1) end, S0, VVs),
+ icrt_export(Vs, Vt, In, I, [{V,{S,used,Ls}}|Acc]);
+icrt_export([{V,_}|Vs0], [{V,{_,_,Ls}}|Vt], In, I, Acc) ->
+ %% V was either unsafe or bound and has now been reused. It may also have
+ %% been an export but as it was not matched by the previous clause, it means
+ %% it has been changed to 'bound' in at least one clause because it was used
+ %% in a pattern.
+ Vs = lists:dropwhile(fun ({K,_}) -> K =:= V end, Vs0),
+ icrt_export(Vs, Vt, In, I, [{V,{bound,used,Ls}}|Acc]);
+icrt_export([{V1,_}|_]=Vs, [{V2,_}|Vt], In, I, Acc) when V1 > V2 ->
+ %% V2 was already in scope and has not been reused in any clause.
+ icrt_export(Vs, Vt, In, I, Acc);
+icrt_export([{V,_}|_]=Vs0, Vt, In, I, Acc) ->
+ %% V is a new variable.
+ {VVs,Vs} = lists:partition(fun ({K,_}) -> K =:= V end, Vs0),
+ F = fun ({_,{S,U,Ls}}, {AccI,AccS0,AccLs0}) ->
+ AccS = case {S,AccS0} of
+ {{unsafe,_},{unsafe,_}} ->
+ %% V was found unsafe in a previous clause, mark
+ %% it as unsafe for the whole parent expression.
+ {unsafe,In};
+ {{unsafe,_},_} ->
+ %% V was unsafe in a clause, keep that state and
+ %% generalize it to the whole expression if it
+ %% is found unsafe in another one.
+ S;
+ _ ->
+ %% V is either bound or exported, keep original
+ %% state.
+ AccS0
+ end,
+ AccLs = case U of
+ used -> AccLs0;
+ unused -> merge_lines(AccLs0, Ls)
+ end,
+ {AccI + 1,AccS,AccLs}
+ end,
+ %% Initial state is exported from the current expression.
+ {Count,S1,Ls} = foldl(F, {0,{export,In},[]}, VVs),
+ S = case Count of
+ I ->
+ %% V was found in all clauses, keep computed state.
+ S1;
+ _ ->
+ %% V was not bound in some clauses, mark as unsafe.
+ {unsafe,In}
+ end,
+ U = case Ls of [] -> used; _ -> unused end,
+ icrt_export(Vs, Vt, In, I, [{V,{S,U,Ls}}|Acc]);
+icrt_export([], _, _, _, Acc) ->
+ reverse(Acc).
handle_comprehension(E, Qs, Vt0, St0) ->
{Vt1, Uvt, St1} = lc_quals(Qs, Vt0, St0),
@@ -3163,7 +3184,8 @@ fun_clauses(Cs, Vt, St) ->
{Cvt,St1} = fun_clause(C, Vt, St0),
{vtmerge(Cvt, Bvt0),St1}
end, {[],St#lint{recdef_top = false}}, Cs),
- {vt_no_unused(vtold(Bvt, Vt)),St2#lint{recdef_top = OldRecDef}}.
+ Uvt = vt_no_unsafe(vt_no_unused(vtold(Bvt, Vt))),
+ {Uvt,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
@@ -3277,19 +3299,24 @@ pat_binsize_var(V, Line, Vt, Bvt, St) ->
%% exported vars are probably safe, warn only if warn_export_vars is
%% set.
-expr_var(V, Line, Vt, St0) ->
+expr_var(V, Line, Vt, St) ->
case orddict:find(V, Vt) of
{ok,{bound,_Usage,Ls}} ->
- {[{V,{bound,used,Ls}}],St0};
+ {[{V,{bound,used,Ls}}],St};
{ok,{{unsafe,In},_Usage,Ls}} ->
{[{V,{bound,used,Ls}}],
- add_error(Line, {unsafe_var,V,In}, St0)};
+ add_error(Line, {unsafe_var,V,In}, St)};
{ok,{{export,From},_Usage,Ls}} ->
- {[{V,{bound,used,Ls}}],
- exported_var(Line, V, From, St0)};
+ case is_warn_enabled(export_vars, St) of
+ true ->
+ {[{V,{bound,used,Ls}}],
+ add_warning(Line, {exported_var,V,From}, St)};
+ false ->
+ {[{V,{{export,From},used,Ls}}],St}
+ end;
error ->
{[{V,{bound,used,[Line]}}],
- add_error(Line, {unbound_var,V}, St0)}
+ add_error(Line, {unbound_var,V}, St)}
end.
exported_var(Line, V, From, St) ->
@@ -3353,17 +3380,12 @@ vtupdate(Uvt, Vt0) ->
{S, merge_used(U1, U2), merge_lines(L1, L2)}
end, Uvt, Vt0).
-%% vtexport([Variable], From, VarTable) -> VarTable.
-%% vtunsafe([Variable], From, VarTable) -> VarTable.
-%% Add the variables to VarTable either as exported from From or as unsafe.
+%% vtunsafe(From, UpdVarTable, VarTable) -> UnsafeVarTable.
+%% Return all new variables in UpdVarTable as unsafe.
-vtexport(Vs, {InTag,FileLine}, Vt0) ->
+vtunsafe({Tag,FileLine}, Uvt, Vt) ->
{_File,Line} = loc(FileLine),
- vtupdate([{V,{{export,{InTag,Line}},unused,[]}} || V <- Vs], Vt0).
-
-vtunsafe(Vs, {InTag,FileLine}, Vt0) ->
- {_File,Line} = loc(FileLine),
- vtupdate([{V,{{unsafe,{InTag,Line}},unused,[]}} || V <- Vs], Vt0).
+ [{V,{{unsafe,{Tag,Line}},U,Ls}} || {V,{_,U,Ls}} <- vtnew(Uvt, Vt)].
%% vtmerge(VarTable, VarTable) -> VarTable.
%% Merge two variables tables generating a new vartable. Give priority to
@@ -3416,8 +3438,6 @@ vtsubtract(New, Old) ->
vtold(New, Old) ->
orddict:filter(fun (V, _How) -> orddict:is_key(V, Old) end, New).
-vtnames(Vt) -> [ V || {V,_How} <- Vt ].
-
vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt,
case S of
{unsafe,_} -> false;
@@ -3426,29 +3446,6 @@ vt_no_unsafe(Vt) -> [V || {_,{S,_U,_L}}=V <- Vt,
vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused].
-%% vunion(VarTable1, VarTable2) -> [VarName].
-%% vunion([VarTable]) -> [VarName].
-%% vintersection(VarTable1, VarTable2) -> [VarName].
-%% vintersection([VarTable]) -> [VarName].
-%% Union/intersection of names of vars in VarTable.
-
--ifdef(NOTUSED).
-vunion(Vs1, Vs2) -> ordsets:union(vtnames(Vs1), vtnames(Vs2)).
-
-vunion(Vss) -> foldl(fun (Vs, Uvs) ->
- ordsets:union(vtnames(Vs), Uvs)
- end, [], Vss).
-
-vintersection(Vs1, Vs2) -> ordsets:intersection(vtnames(Vs1), vtnames(Vs2)).
--endif.
-
-vintersection([Vs]) ->
- vtnames(Vs); %Boundary conditions!!!
-vintersection([Vs|Vss]) ->
- ordsets:intersection(vtnames(Vs), vintersection(Vss));
-vintersection([]) ->
- [].
-
%% copy_expr(Expr, Line) -> Expr.
%% Make a copy of Expr converting all line numbers to Line.