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.erl64
1 files changed, 52 insertions, 12 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 648ff349a4..1e5f962375 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -365,6 +365,12 @@ format_error(callback_wrong_arity) ->
format_error({imported_predefined_type, Name}) ->
io_lib:format("referring to built-in type ~w as a remote type; "
"please take out the module name", [Name]);
+format_error({not_exported_opaque, {TypeName, Arity}}) ->
+ io_lib:format("opaque type ~w~s is not exported",
+ [TypeName, gen_type_paren(Arity)]);
+format_error({underspecified_opaque, {TypeName, Arity}}) ->
+ io_lib:format("opaque type ~w~s is underspecified and therefore meaningless",
+ [TypeName, gen_type_paren(Arity)]);
%% --- obsolete? unused? ---
format_error({format_error, {Fmt, Args}}) ->
io_lib:format(Fmt, Args);
@@ -851,7 +857,8 @@ post_traversal_check(Forms, St0) ->
StC = check_untyped_records(Forms, StB),
StD = check_on_load(StC),
StE = check_unused_records(Forms, StD),
- check_callback_information(StE).
+ StF = check_local_opaque_types(StE),
+ check_callback_information(StF).
%% check_behaviour(State0) -> State
%% Check that the behaviour attribute is valid.
@@ -1916,9 +1923,6 @@ gexpr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,F}},As}, Vt, St0) ->
true -> {Asvt,St1};
false -> {Asvt,add_error(Line, illegal_guard_expr, St1)}
end;
-gexpr({call,L,{tuple,Lt,[{atom,Lm,erlang},{atom,Lf,F}]},As}, Vt, St0) ->
- St = add_warning(L, deprecated_tuple_fun, St0),
- gexpr({call,L,{remote,Lt,{atom,Lm,erlang},{atom,Lf,F}},As}, Vt, St);
gexpr({op,Line,Op,A}, Vt, St0) ->
{Avt,St1} = gexpr(A, Vt, St0),
case is_gexpr_op(Op, 1) of
@@ -2557,15 +2561,24 @@ 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.
Types = [T || {typed_record_field, _, T} <- Fields],
check_type({type, -1, product, Types}, St0);
-type_def(_Attr, Line, TypeName, ProtoType, Args, St0) ->
+type_def(Attr, Line, TypeName, ProtoType, Args, St0) ->
TypeDefs = St0#lint.types,
Arity = length(Args),
TypePair = {TypeName, Arity},
+ Info = #typeinfo{attr = Attr, line = Line},
+ StoreType =
+ fun(St) ->
+ NewDefs = dict:store(TypePair, Info, TypeDefs),
+ CheckType = {type, -1, product, [ProtoType|Args]},
+ check_type(CheckType, St#lint{types=NewDefs})
+ end,
case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of
true ->
case dict:is_key(TypePair, default_types()) of
@@ -2575,20 +2588,29 @@ type_def(_Attr, Line, TypeName, ProtoType, Args, St0) ->
true ->
Warn = {new_builtin_type, TypePair},
St1 = add_warning(Line, Warn, St0),
- NewDefs = dict:store(TypePair, Line, TypeDefs),
- CheckType = {type, -1, product, [ProtoType|Args]},
- check_type(CheckType, St1#lint{types=NewDefs});
+ StoreType(St1);
false ->
add_error(Line, {builtin_type, TypePair}, St0)
end;
false -> add_error(Line, {redefine_type, TypePair}, St0)
end;
false ->
- NewDefs = dict:store(TypePair, Line, TypeDefs),
- CheckType = {type, -1, product, [ProtoType|Args]},
- check_type(CheckType, St0#lint{types=NewDefs})
+ St1 = case
+ Attr =:= opaque andalso
+ is_underspecified(ProtoType, Arity)
+ of
+ true ->
+ Warn = {underspecified_opaque, TypePair},
+ add_warning(Line, Warn, St0);
+ false -> St0
+ end,
+ StoreType(St1)
end.
+is_underspecified({type,_,term,[]}, 0) -> true;
+is_underspecified({type,_,any,[]}, 0) -> true;
+is_underspecified(_ProtType, _Arity) -> false.
+
check_type(Types, St) ->
{SeenVars, St1} = check_type(Types, dict:new(), St),
dict:fold(fun(Var, {seen_once, Line}, AccSt) ->
@@ -2898,7 +2920,7 @@ check_unused_types(Forms, #lint{usage=Usage, types=Ts, exp_types=ExpTs}=St) ->
fun(_Type, -1, AccSt) ->
%% Default type
AccSt;
- (Type, FileLine, AccSt) ->
+ (Type, #typeinfo{line = FileLine}, AccSt) ->
case loc(FileLine) of
{FirstFile, _} ->
case gb_sets:is_member(Type, UsedTypes) of
@@ -2917,6 +2939,24 @@ check_unused_types(Forms, #lint{usage=Usage, types=Ts, exp_types=ExpTs}=St) ->
St
end.
+check_local_opaque_types(St) ->
+ #lint{types=Ts, exp_types=ExpTs} = St,
+ FoldFun =
+ fun(_Type, -1, AccSt) ->
+ %% Default type
+ AccSt;
+ (_Type, #typeinfo{attr = type}, AccSt) ->
+ AccSt;
+ (Type, #typeinfo{attr = opaque, line = FileLine}, AccSt) ->
+ case gb_sets:is_element(Type, ExpTs) of
+ true -> AccSt;
+ false ->
+ Warn = {not_exported_opaque,Type},
+ add_warning(FileLine, Warn, AccSt)
+ end
+ end,
+ dict:fold(FoldFun, St, Ts).
+
%% icrt_clauses(Clauses, In, ImportVarTable, State) ->
%% {NewVts,State}.