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.erl185
1 files changed, 133 insertions, 52 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 269e4b34cf..c4c94fbee4 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -80,13 +80,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-type fa() :: {atom(), arity()}. % function+arity
-type ta() :: {atom(), arity()}. % type+arity
+-record(typeinfo, {attr, line}).
+
%% Usage of records, functions, and imports. The variable table, which
%% is passed on as an argument, holds the usage of variables.
-record(usage, {
calls = dict:new(), %Who calls who
imported = [], %Actually imported functions
- used_records=sets:new() :: sets:set(),%Used record definitions
- used_types = dict:new() :: dict:dict()%Used type definitions
+ used_records = sets:new() %Used record definitions
+ :: sets:set(atom()),
+ used_types = dict:new() %Used type definitions
+ :: dict:dict(ta(), line())
}).
%% Define the lint state record.
@@ -95,13 +99,17 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
-record(lint, {state=start :: 'start' | 'attribute' | 'function',
module=[], %Module
behaviour=[], %Behaviour
- exports=gb_sets:empty() :: gb_sets:set(),%Exports
- imports=[], %Imports
+ exports=gb_sets:empty() :: gb_sets:set(fa()),%Exports
+ imports=[] :: [fa()], %Imports, an orddict()
compile=[], %Compile flags
- records=dict:new() :: dict:dict(), %Record definitions
- locals=gb_sets:empty() :: gb_sets:set(),%All defined functions (prescanned)
- no_auto=gb_sets:empty() :: gb_sets:set() | 'all',%Functions explicitly not autoimported
- defined=gb_sets:empty() :: gb_sets:set(),%Defined fuctions
+ records=dict:new() %Record definitions
+ :: dict:dict(atom(), {line(),Fields :: term()}),
+ locals=gb_sets:empty() %All defined functions (prescanned)
+ :: gb_sets:set(fa()),
+ no_auto=gb_sets:empty() %Functions explicitly not autoimported
+ :: gb_sets:set(fa()) | 'all',
+ defined=gb_sets:empty() %Defined fuctions
+ :: gb_sets:set(fa()),
on_load=[] :: [fa()], %On-load function
on_load_line=0 :: line(), %Line for on_load
clashes=[], %Exported functions named as BIFs
@@ -116,12 +124,16 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
%outside any fun or lc
xqlc= false :: boolean(), %true if qlc.hrl included
new = false :: boolean(), %Has user-defined 'new/N'
- called= [] :: [{fa(),line()}], %Called functions
+ called= [] :: [{fa(),line()}], %Called functions
usage = #usage{} :: #usage{},
- specs = dict:new() :: dict:dict(), %Type specifications
- callbacks = dict:new() :: dict:dict(), %Callback types
- types = dict:new() :: dict:dict(), %Type definitions
- exp_types=gb_sets:empty():: gb_sets:set()%Exported types
+ specs = dict:new() %Type specifications
+ :: dict:dict(mfa(), line()),
+ callbacks = dict:new() %Callback types
+ :: dict:dict(mfa(), line()),
+ types = dict:new() %Type definitions
+ :: dict:dict(ta(), #typeinfo{}),
+ exp_types=gb_sets:empty() %Exported types
+ :: gb_sets:set(ta())
}).
-type lint_state() :: #lint{}.
@@ -225,6 +237,8 @@ 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_bin_pattern) ->
@@ -317,10 +331,14 @@ 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; "
+%% 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; "
"its (re)definition is allowed only until the next release",
- [TypeName, gen_type_paren(Arity)]);
+ [TypeName]);
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)]);
@@ -1168,7 +1186,7 @@ export_type(Line, ETs, #lint{usage = Usage, exp_types = ETs0} = St0) ->
add_error(Line, {bad_export_type, ETs}, St0)
end.
--spec exports(lint_state()) -> gb_sets:set().
+-spec exports(lint_state()) -> gb_sets:set(fa()).
exports(#lint{compile = Opts, defined = Defs, exports = Es}) ->
case lists:member(export_all, Opts) of
@@ -1385,19 +1403,20 @@ 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 expr(KP, [], St0) of
- {[],_} ->
- {Pvt,Bvt1,St1} = pattern(VP, Vt, Old, Bvt, St0),
- {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt0, Bvt1),
- St1};
- {[Var|_],_} ->
- Error = {illegal_map_key_variable,element(1, Var)},
- {Psvt,Bvt0,add_error(L, Error, St0)}
- end
- end, {[],[],St}, Ps);
+ 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, 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({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) ->
@@ -2237,9 +2256,10 @@ check_assoc_fields([], 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,Var} -> add_error(Line, {illegal_map_key_variable,Var}, St)
- end,
+ 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),
{Vts,St3} = map_fields(Fs, Vt, St2, F),
{vtupdate(Pvt, Vts),St3};
@@ -2298,11 +2318,64 @@ 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) ->
case expr(K,[],St) of
- {[],_} -> true;
+ {[],_} ->
+ is_valid_map_key_value(K);
{[Var|_],_} ->
- {false,element(1,Var)}
+ {false,variable,element(1,Var)}
+ end.
+
+is_valid_map_key_value(K) ->
+ case K of
+ {char,_,_} -> true;
+ {integer,_,_} -> true;
+ {float,_,_} -> true;
+ {string,_,_} -> true;
+ {nil,_} -> true;
+ {atom,_,_} -> true;
+ {cons,_,H,T} ->
+ 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)
+ 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) andalso foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
+ end,true,Ps);
+ {map,_,Ps} ->
+ foldl(fun
+ ({Tag,_,Ke,Ve},B) when Tag =:= map_field_assoc;
+ Tag =:= map_field_exact ->
+ B andalso is_valid_map_key_value(Ke)
+ andalso is_valid_map_key_value(Ve)
+ end, true, Ps);
+ {record,_,_,Fs} ->
+ foldl(fun
+ ({record_field,_,Ke,Ve},B) ->
+ 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
+ % invalid binary expressions are later checked in
+ % core and kernel
+ foldl(fun
+ ({bin_element,_,E,_,_},B) ->
+ B andalso is_valid_map_key_value(E)
+ end,true,Es);
+ _ -> false
end.
%% record_def(Line, RecordName, [RecField], State) -> State.
@@ -2517,8 +2590,6 @@ find_field(_F, []) -> error.
%% Attr :: 'type' | 'opaque'
%% Checks that a type definition is valid.
--record(typeinfo, {attr, line}).
-
type_def(_Attr, _Line, {record, _RecName}, Fields, [], St0) ->
%% The record field names and such are checked in the record format.
%% We only need to check the types.
@@ -2539,23 +2610,30 @@ type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
true ->
case is_obsolete_builtin_type(TypePair) of
true -> StoreType(St0);
- 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
+ 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
end;
false ->
case
- dict:is_key(TypePair, TypeDefs)
- orelse is_var_arity_type(TypeName)
+ dict:is_key(TypePair, TypeDefs) orelse
+ is_var_arity_type(TypeName)
of
- true -> add_error(Line, {redefine_type, TypePair}, St0);
+ 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;
false ->
St1 = case
Attr =:= opaque andalso
@@ -2727,6 +2805,7 @@ 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;
@@ -2759,7 +2838,6 @@ 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({map, 0}) -> true;
is_default_type({maybe_improper_list, 0}) -> true;
is_default_type({maybe_improper_list, 2}) -> true;
is_default_type({mfa, 0}) -> true;
@@ -2790,7 +2868,10 @@ is_default_type({timeout, 0}) -> true;
is_default_type({var, 1}) -> true;
is_default_type(_) -> false.
-is_newly_introduced_builtin_type({Name, _}) when is_atom(Name) -> 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.
is_obsolete_builtin_type(TypePair) ->
obsolete_builtin_type(TypePair) =/= no.