File 2623-Add-options-for-suppressing-warnings-about-removed-f.patch of Package erlang

From 1a58a7c0a9af1eb98ddfecbc6157325f2c869eb1 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 4 Apr 2019 06:09:31 +0200
Subject: [PATCH 5/5] Add options for suppressing warnings about removed
 functions

An appliction outside of OTP may want to reuse then name of a module
that was previously included in OTP. Therefore, there should be
a way to suppress warnings for removed functions.
---
 lib/compiler/doc/src/compile.xml   | 16 +++++++++++++
 lib/edoc/src/edoc_data.erl         |  2 ++
 lib/stdlib/src/erl_lint.erl        | 46 +++++++++++++++++++++++++++++++++-----
 lib/stdlib/test/erl_lint_SUITE.erl | 24 +++++++++++++++++++-
 4 files changed, 82 insertions(+), 6 deletions(-)

diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml
index 5219ba0f5d..549b1049d8 100644
--- a/lib/compiler/doc/src/compile.xml
+++ b/lib/compiler/doc/src/compile.xml
@@ -632,6 +632,22 @@ module.beam: module.erl \
 	    to be deprecated.</p>
           </item>
 
+	  <tag><c>nowarn_removed</c></tag>
+          <item>
+            <p>Turns off warnings for calls to functions that have
+            been removed. Default is to emit warnings for every call
+            to a function known by the compiler to have been recently
+            removed from Erlang/OTP.</p>
+          </item>
+
+	  <tag><c>{nowarn_removed, ModulesOrMFAs}</c></tag>
+          <item>
+            <p>Turns off warnings for calls to modules or functions
+            that have been removed. Default is to emit warnings for
+            every call to a function known by the compiler to have
+            been recently removed from Erlang/OTP.</p>
+          </item>
+
 	  <tag><c>nowarn_obsolete_guard</c></tag>
           <item>
             <p>Turns off warnings for calls to old type testing BIFs, 
diff --git a/lib/edoc/src/edoc_data.erl b/lib/edoc/src/edoc_data.erl
index 7c077d3acd..a8373d6536 100644
--- a/lib/edoc/src/edoc_data.erl
+++ b/lib/edoc/src/edoc_data.erl
@@ -345,6 +345,8 @@ deprecated(Repl, Env) ->
 deprecated(Desc) ->
     [{deprecated, description(Desc)}].
 
+-dialyzer({no_match, replacement_function/2}).
+
 replacement_function(M0, {M,F,A}) when is_list(A) ->
     %% refer to the largest listed arity - the most general version
     replacement_function(M0, {M,F,lists:last(lists:sort(A))});
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 3ec78a2667..00fd731e1d 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -79,6 +79,8 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
 -type fa()   :: {atom(), arity()}.   % function+arity
 -type ta()   :: {atom(), arity()}.   % type+arity
 
+-type module_or_mfa() :: module() | mfa().
+
 -record(typeinfo, {attr, line}).
 
 %% Usage of records, functions, and imports. The variable table, which
@@ -122,6 +124,8 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
                    :: erl_anno:anno(),
 	       clashes=[],			%Exported functions named as BIFs
                not_deprecated=[],               %Not considered deprecated
+               not_removed=gb_sets:empty()      %Not considered removed
+                   :: gb_sets:set(module_or_mfa()),
                func=[],                         %Current function
                warn_format=0,                   %Warn format calls
 	       enabled_warnings=[],		%All enabled warnings (ordset).
@@ -587,7 +591,10 @@ start(File, Opts) ->
 		      false, Opts)},
          {get_stacktrace,
           bool_option(warn_get_stacktrace, nowarn_get_stacktrace,
-                      true, Opts)}
+                      true, Opts)},
+         {removed,
+          bool_option(warn_removed, nowarn_removed,
+                      true, Opts)}
 	],
     Enabled1 = [Category || {Category,true} <- Enabled0],
     Enabled = ordsets:from_list(Enabled1),
@@ -684,8 +691,9 @@ forms(Forms0, St0) ->
 						    no_auto = AutoImportSuppressed}),
     St2 = bif_clashes(Forms, St1),
     St3 = not_deprecated(Forms, St2),
-    St4 = foldl(fun form/2, pre_scan(Forms, St3), Forms),
-    post_traversal_check(Forms, St4).
+    St4 = not_removed(St3),
+    St5 = foldl(fun form/2, pre_scan(Forms, St4), Forms),
+    post_traversal_check(Forms, St5).
 
 pre_scan([{attribute,L,compile,C} | Fs], St) ->
     case is_warn_enabled(export_all, St) andalso
@@ -856,6 +864,15 @@ not_deprecated(Forms, #lint{compile=Opts}=St0) ->
     St1 = func_line_warning(bad_nowarn_deprecated_function, Bad, St0),
     St1#lint{not_deprecated = ordsets:from_list(Nowarn)}.
 
+%% not_removed(State0) -> State
+
+not_removed(#lint{compile=Opts}=St) ->
+    %% There are no line numbers in St#lint.compile.
+    Nowarn = [MFA ||
+                 {nowarn_removed, MFAs0} <- Opts,
+                 MFA <- lists:flatten([MFAs0])],
+    St#lint{not_removed = gb_sets:from_list(Nowarn)}.
+
 %% The nowarn_bif_clash directive is not only deprecated, it's actually an error from R14A
 disallowed_compile_flags(Forms, St0) ->
     %% There are (still) no line numbers in St0#lint.compile.
@@ -3700,13 +3717,23 @@ deprecated_function(Line, M, F, As, St) ->
 		    add_warning(Line, {deprecated, MFA, Replacement, Rel}, St)
             end;
 	{removed, String} when is_list(String) ->
-	    add_warning(Line, {removed, MFA, String}, St);
+	    add_removed_warning(Line, MFA, {removed, MFA, String}, St);
 	{removed, Replacement, Rel} ->
-	    add_warning(Line, {removed, MFA, Replacement, Rel}, St);
+	    add_removed_warning(Line, MFA, {removed, MFA, Replacement, Rel}, St);
         no ->
 	    St
     end.
 
+add_removed_warning(Line, {M, _, _}=MFA, Warning, #lint{not_removed=NotRemoved}=St) ->
+    case is_warn_enabled(removed, St) andalso
+        not gb_sets:is_element(M, NotRemoved) andalso
+        not gb_sets:is_element(MFA, NotRemoved) of
+        true ->
+            add_warning(Line, Warning, St);
+        false ->
+            St
+    end.
+
 check_get_stacktrace(Line, erlang, get_stacktrace, [], St) ->
     case St of
         #lint{catch_scope=none} ->
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 6d604794e7..939cc1024c 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -2108,7 +2108,29 @@ otp_5362(Config) when is_list(Config) ->
 	   [],
 	   {warnings,
             [{1,erl_lint,{removed,{regexp,match,1},
-			  "removed in R15; use the re module instead"}}]}}
+			  "removed in R15; use the re module instead"}}]}},
+
+	  {nowarn_call_removed_function_1,
+	   <<"t(X) -> erlang:hash(X, 10000).">>,
+	   [{nowarn_removed,{erlang,hash,2}}],
+	   []},
+
+	  {nowarn_call_removed_function_2,
+	   <<"t(X) -> os_mon_mib:any_function_really(erlang:hash(X, 10000)).">>,
+	   [nowarn_removed],
+	   []},
+
+	  {call_removed_module,
+	   <<"t(X) -> os_mon_mib:any_function_really(X).">>,
+	   [],
+           {warnings,[{1,erl_lint,
+                       {removed,{os_mon_mib,any_function_really,1},
+                        "was removed in 22.0"}}]}},
+
+	  {nowarn_call_removed_module,
+	   <<"t(X) -> os_mon_mib:any_function_really(X).">>,
+	   [{nowarn_removed,os_mon_mib}],
+	   []}
 
 	 ],
 
-- 
2.16.4

openSUSE Build Service is sponsored by