aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_lint.erl
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2015-06-26 14:09:43 +0200
committerHans Bolinder <[email protected]>2015-09-15 14:15:49 +0200
commitd9daff6d87c217ba7d3cba00642710e473e9b226 (patch)
tree1a77018babaf2caf52d6bde906daaf15a492b926 /lib/stdlib/src/erl_lint.erl
parent195393b00e0a5b83526a2bca504fe32edd6dc989 (diff)
downloadotp-d9daff6d87c217ba7d3cba00642710e473e9b226.tar.gz
otp-d9daff6d87c217ba7d3cba00642710e473e9b226.tar.bz2
otp-d9daff6d87c217ba7d3cba00642710e473e9b226.zip
stdlib: Remove deprecated functions in erl_parse and erl_scan
The recently added module erl_anno can no longer handle negative line numbers.
Diffstat (limited to 'lib/stdlib/src/erl_lint.erl')
-rw-r--r--lib/stdlib/src/erl_lint.erl22
1 files changed, 10 insertions, 12 deletions
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index c4cb5fdc80..a5f0e7dbd3 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -31,12 +31,8 @@
-export([is_guard_expr/1]).
-export([bool_option/4,value_option/3,value_option/7]).
--export([modify_line/2]).
-
-import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]).
--deprecated([{modify_line, 2, next_major_release}]).
-
%% bool_option(OnOpt, OffOpt, Default, Options) -> boolean().
%% value_option(Flag, Default, Options) -> Value.
%% value_option(Flag, Default, OnOpt, OnVal, OffOpt, OffVal, Options) ->
@@ -79,7 +75,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
%%-define(DEBUGF(X,Y), io:format(X, Y)).
-define(DEBUGF(X,Y), void).
--type line() :: erl_anno:line(). % a convenient alias
+-type line() :: erl_anno:anno(). % a convenient alias
-type fa() :: {atom(), arity()}. % function+arity
-type ta() :: {atom(), arity()}. % type+arity
@@ -238,6 +234,9 @@ format_error({removed, MFA, ReplacementMFA, Rel}) ->
"use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]);
format_error({removed, MFA, String}) when is_list(String) ->
io_lib:format("~s: ~s", [format_mfa(MFA), String]);
+format_error({removed_type, MNA, ReplacementMNA, Rel}) ->
+ io_lib:format("the type ~s was removed in ~s; use ~s instead",
+ [format_mna(MNA), Rel, format_mna(ReplacementMNA)]);
format_error({obsolete_guard, {F, A}}) ->
io_lib:format("~p/~p obsolete", [F, A]);
format_error({too_many_arguments,Arity}) ->
@@ -413,6 +412,9 @@ format_mfa({M, F, A}) when is_integer(A) ->
format_mf(M, F, ArityString) when is_atom(M), is_atom(F) ->
atom_to_list(M) ++ ":" ++ atom_to_list(F) ++ "/" ++ ArityString.
+format_mna({M, N, A}) when is_integer(A) ->
+ atom_to_list(M) ++ ":" ++ atom_to_list(N) ++ gen_type_paren(A).
+
format_where(L) when is_integer(L) ->
io_lib:format("(line ~p)", [L]);
format_where({L,C}) when is_integer(L), is_integer(C) ->
@@ -3482,13 +3484,6 @@ vt_no_unused(Vt) -> [V || {_,{_,U,_L}}=V <- Vt, U =/= unused].
copy_expr(Expr, Anno) ->
erl_parse:map_anno(fun(_A) -> Anno end, Expr).
-%% modify_line(Form, Fun) -> Form
-%% modify_line(Expression, Fun) -> Expression
-%% Applies Fun to each line number occurrence.
-
-modify_line(T, F0) ->
- erl_parse:map_anno(F0, T).
-
%% Check a record_info call. We have already checked that it is not
%% shadowed by an import.
@@ -3557,6 +3552,7 @@ deprecated_function(Line, M, F, As, St) ->
St
end.
+-dialyzer({no_match, deprecated_type/5}).
deprecated_type(L, M, N, As, St) ->
NAs = length(As),
case otp_internal:obsolete_type(M, N, NAs) of
@@ -3567,6 +3563,8 @@ deprecated_type(L, M, N, As, St) ->
false ->
St
end;
+ {removed, Replacement, Rel} ->
+ add_warning(L, {removed_type, {M,N,NAs}, Replacement, Rel}, St);
no ->
St
end.