aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_lint.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2012-09-21 15:43:33 +0200
committerHans Bolinder <[email protected]>2012-09-26 16:14:39 +0200
commitd66bc8561265e699df4706e88611b67d243ba933 (patch)
treead0880d709c2e0bfa359e881c6aef2bd93cd4b4a /lib/stdlib/src/erl_lint.erl
parent69bf3ed7ca0545fa350b3b95b650d79de59b85cd (diff)
downloadotp-d66bc8561265e699df4706e88611b67d243ba933.tar.gz
otp-d66bc8561265e699df4706e88611b67d243ba933.tar.bz2
otp-d66bc8561265e699df4706e88611b67d243ba933.zip
Warn for opaque types that are not exported
Diffstat (limited to 'lib/stdlib/src/erl_lint.erl')
-rw-r--r--lib/stdlib/src/erl_lint.erl35
1 files changed, 30 insertions, 5 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 97dacac0a4..a03abfaf80 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -365,6 +365,9 @@ 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)]);
%% --- obsolete? unused? ---
format_error({format_error, {Fmt, Args}}) ->
io_lib:format(Fmt, Args);
@@ -851,7 +854,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.
@@ -2554,15 +2558,18 @@ 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},
case (dict:is_key(TypePair, TypeDefs) orelse is_var_arity_type(TypeName)) of
true ->
case dict:is_key(TypePair, default_types()) of
@@ -2572,7 +2579,7 @@ 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),
+ NewDefs = dict:store(TypePair, Info, TypeDefs),
CheckType = {type, -1, product, [ProtoType|Args]},
check_type(CheckType, St1#lint{types=NewDefs});
false ->
@@ -2581,7 +2588,7 @@ type_def(_Attr, Line, TypeName, ProtoType, Args, St0) ->
false -> add_error(Line, {redefine_type, TypePair}, St0)
end;
false ->
- NewDefs = dict:store(TypePair, Line, TypeDefs),
+ NewDefs = dict:store(TypePair, Info, TypeDefs),
CheckType = {type, -1, product, [ProtoType|Args]},
check_type(CheckType, St0#lint{types=NewDefs})
end.
@@ -2895,7 +2902,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
@@ -2914,6 +2921,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}.