File 2071-Don-t-crash-when-obsolete-guard-overrides-local-func.patch of Package erlang

From 8a04dd4dd2d479efe488b0bed118e10559835fb6 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 11 Aug 2016 12:56:06 +0200
Subject: [PATCH 1/2] Don't crash when obsolete guard overrides local function

The compiler would crash in v3_codegen when trying to compile the
following code:

  is_port(_) -> false.
  foo(P) when port(P) -> ok.

We *could* have the compiler interpret the code as:

  is_port(_) -> false.
  foo(P) when erlang:is_port(P) -> ok.

But that would encourage using the obsolete form of the guard tests.
Note that the following code is illegal:

  is_port(_) -> false.
  foo(P) when is_port(P) -> ok.

It produces the following diagnostic:

  call to local/imported function is_port/1 is illegal in guard

Therefore, we should refuse to compile the code.
---
 lib/stdlib/src/erl_lint.erl        | 28 +++++++++++++++++++++-------
 lib/stdlib/test/erl_lint_SUITE.erl | 10 +++++++++-
 2 files changed, 30 insertions(+), 8 deletions(-)

diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index e9332ce..5ec9b90 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -238,7 +238,11 @@ 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]);
+    io_lib:format("~p/~p obsolete (use is_~p/~p)", [F, A, F, A]);
+format_error({obsolete_guard_overridden,Test}) ->
+    io_lib:format("obsolete ~s/1 (meaning is_~s/1) is illegal when "
+		  "there is a local/imported function named is_~p/1 ",
+		  [Test,Test,Test]);
 format_error({too_many_arguments,Arity}) ->
     io_lib:format("too many arguments (~w) - "
 		  "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]);
@@ -3618,16 +3622,26 @@ obsolete_guard({call,Line,{atom,Lr,F},As}, St0) ->
 	false ->
 	    deprecated_function(Line, erlang, F, As, St0);
 	true ->
-	    case is_warn_enabled(obsolete_guard, St0) of
-		true ->
-		    add_warning(Lr,{obsolete_guard, {F, Arity}}, St0);
-		false ->
-		    St0
-	    end
+	    St = case is_warn_enabled(obsolete_guard, St0) of
+		     true ->
+			 add_warning(Lr, {obsolete_guard, {F, Arity}}, St0);
+		     false ->
+			 St0
+		 end,
+	    test_overriden_by_local(Lr, F, Arity, St)
     end;
 obsolete_guard(_G, St) ->
     St.
 
+test_overriden_by_local(Line, OldTest, Arity, St) ->
+    ModernTest = list_to_atom("is_"++atom_to_list(OldTest)),
+    case is_local_function(St#lint.locals, {ModernTest, Arity}) of
+	true ->
+	    add_error(Line, {obsolete_guard_overridden,OldTest}, St);
+	false ->
+	    St
+    end.
+
 %% keyword_warning(Line, Atom, State) -> State.
 %%  Add warning for atoms that will be reserved keywords in the future.
 %%  (Currently, no such keywords to warn for.)
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index d916eb3..4ee3950 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1554,7 +1554,15 @@ guard(Config) when is_list(Config) ->
             [],
             {errors,[{1,erl_lint,illegal_guard_expr},
                      {2,erl_lint,illegal_guard_expr}],
-             []}}
+             []}},
+           {guard10,
+            <<"is_port(_) -> false.
+               t(P) when port(P) -> ok.
+            ">>,
+            [],
+            {error,
+	     [{2,erl_lint,{obsolete_guard_overridden,port}}],
+	     [{2,erl_lint,{obsolete_guard,{port,1}}}]}}
 	  ],
     [] = run(Config, Ts1),
     ok.
-- 
2.10.0

openSUSE Build Service is sponsored by