File 1259-Fix-a-bug-in-Dialyzer-related-to-call-site-analysis.patch of Package erlang

From b13412d2e4331fa426a6722a04310cbcbf1731d6 Mon Sep 17 00:00:00 2001
From: Stavros Aronis <aronisstav@gmail.com>
Date: Wed, 8 Jun 2016 13:13:04 +0200
Subject: [PATCH] Fix a bug in Dialyzer related to call-site analysis
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

Dialyzer's "dataflow" module is using information from the callgraph to
determine which functions may be called at a particular call-site. Unfortunately
this information can include functions that are certainly not among the possible
choices. We don't want to emit warnings in such cases, so a "reasonable"
compromise is to stay silent if there are many possible funs and at least one of
them can succeed.

Bug reported by Dan Gudmundsson, test shrunk down by Magnus Lång.
---
 lib/dialyzer/src/dialyzer_dataflow.erl             | 58 +++++++++++++++++++---
 .../results/higher_order_discrepancy               |  5 +-
 .../src/higher_order_discrepancy.erl               |  5 ++
 .../test/user_SUITE_data/results/wpc_hlines        |  3 ++
 .../test/user_SUITE_data/src/wpc_hlines.erl        | 22 ++++++++
 5 files changed, 82 insertions(+), 11 deletions(-)
 create mode 100644 lib/dialyzer/test/user_SUITE_data/results/wpc_hlines
 create mode 100644 lib/dialyzer/test/user_SUITE_data/src/wpc_hlines.erl

diff --git a/lib/dialyzer/src/dialyzer_dataflow.erl b/lib/dialyzer/src/dialyzer_dataflow.erl
index 5ab0c39..3349b12 100644
--- a/lib/dialyzer/src/dialyzer_dataflow.erl
+++ b/lib/dialyzer/src/dialyzer_dataflow.erl
@@ -430,17 +430,35 @@ handle_apply(Tree, Map, State) ->
 
 handle_apply_or_call(FunInfoList, Args, ArgTypes, Map, Tree, State) ->
   None = t_none(),
+  %% Call-site analysis may be inaccurate and consider more funs than those that
+  %% are actually possible. If all of them are incorrect, then warnings can be
+  %% emitted. If at least one fun is ok, however, then no warning is emitted,
+  %% just in case the bad ones are not really possible. The last argument is
+  %% used for this, with the following encoding:
+  %%   Initial value: {none, []}
+  %%   First fun checked: {one, <List of warns>}
+  %%   More funs checked: {many, <List of warns>}
+  %% A '{one, []}' can only become '{many, []}'.
+  %% If at any point an fun does not add warnings, then the list is also
+  %% replaced with an empty list.
   handle_apply_or_call(FunInfoList, Args, ArgTypes, Map, Tree, State,
-		       [None || _ <- ArgTypes], None, false).
+		       [None || _ <- ArgTypes], None, false, {none, []}).
 
 handle_apply_or_call([{local, external}|Left], Args, ArgTypes, Map, Tree, State,
-		     _AccArgTypes, _AccRet, _HadExternal) ->
+		     _AccArgTypes, _AccRet, _HadExternal, Warns) ->
+  {HowMany, _} = Warns,
+  NewHowMany =
+    case HowMany of
+      none -> one;
+      _ -> many
+    end,
+  NewWarns = {NewHowMany, []},      
   handle_apply_or_call(Left, Args, ArgTypes, Map, Tree, State,
-		       ArgTypes, t_any(), true);
+		       ArgTypes, t_any(), true, NewWarns);
 handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
 		     Args, ArgTypes, Map, Tree,
                      #state{opaques = Opaques} = State,
-                     AccArgTypes, AccRet, HadExternal) ->
+                     AccArgTypes, AccRet, HadExternal, Warns) ->
   Any = t_any(),
   AnyArgs = [Any || _ <- Args],
   GenSig = {AnyArgs, fun(_) -> t_any() end},
@@ -586,16 +604,32 @@ handle_apply_or_call([{TypeOfApply, {Fun, Sig, Contr, LocalRet}}|Left],
     end,
   NewAccRet = t_sup(AccRet, TotalRet),
   ?debug("NewAccRet: ~s\n", [t_to_string(NewAccRet)]),
+  {NewWarnings, State4} = state__remove_added_warnings(State, State3),
+  {HowMany, OldWarnings} = Warns,
+  NewWarns =
+    case HowMany of
+      none -> {one, NewWarnings};
+      _ ->
+        case OldWarnings =:= [] of
+          true -> {many, []};
+          false ->
+            case NewWarnings =:= [] of
+              true -> {many, []};
+              false -> {many, NewWarnings ++ OldWarnings}
+            end
+        end
+    end,
   handle_apply_or_call(Left, Args, ArgTypes, Map, Tree,
-		       State3, NewAccArgTypes, NewAccRet, HadExternal);
+		       State4, NewAccArgTypes, NewAccRet, HadExternal, NewWarns);
 handle_apply_or_call([], Args, _ArgTypes, Map, _Tree, State,
-		     AccArgTypes, AccRet, HadExternal) ->
+		     AccArgTypes, AccRet, HadExternal, {_, Warnings}) ->
+  State1 = state__add_warnings(Warnings, State),
   case HadExternal of
     false ->
       NewMap = enter_type_lists(Args, AccArgTypes, Map),
-      {State, NewMap, AccRet};
+      {State1, NewMap, AccRet};
     true ->
-      {had_external, State}
+      {had_external, State1}
   end.
 
 apply_fail_reason(FailedSig, FailedBif, FailedContract) ->
@@ -3038,6 +3072,14 @@ state__add_warning(#state{warnings = Warnings, warning_mode = true} = State,
       end
   end.
 
+state__remove_added_warnings(OldState, NewState) ->
+  #state{warnings = OldWarnings} = OldState,
+  #state{warnings = NewWarnings} = NewState,
+  {NewWarnings -- OldWarnings, NewState#state{warnings = OldWarnings}}.
+
+state__add_warnings(Warns, #state{warnings = Warnings} = State) ->
+  State#state{warnings = Warns ++ Warnings}.
+
 -spec state__set_curr_fun(curr_fun(), state()) -> state().
 
 state__set_curr_fun(undefined, State) ->
diff --git a/lib/dialyzer/test/small_SUITE_data/results/higher_order_discrepancy b/lib/dialyzer/test/small_SUITE_data/results/higher_order_discrepancy
index 7ce440a..11b9eca 100644
--- a/lib/dialyzer/test/small_SUITE_data/results/higher_order_discrepancy
+++ b/lib/dialyzer/test/small_SUITE_data/results/higher_order_discrepancy
@@ -1,4 +1,3 @@
 
-higher_order_discrepancy.erl:11: The call higher_order_discrepancy:g('foo') will never return since it differs in the 1st argument from the success typing arguments: ('bar')
-higher_order_discrepancy.erl:14: Function g/1 has no local return
-higher_order_discrepancy.erl:14: The pattern 'bar' can never match the type 'foo'
+higher_order_discrepancy.erl:19: Function g/1 has no local return
+higher_order_discrepancy.erl:19: The pattern 'bar' can never match the type 'foo'
diff --git a/lib/dialyzer/test/small_SUITE_data/src/higher_order_discrepancy.erl b/lib/dialyzer/test/small_SUITE_data/src/higher_order_discrepancy.erl
index ff5ee6b..f9547d4 100644
--- a/lib/dialyzer/test/small_SUITE_data/src/higher_order_discrepancy.erl
+++ b/lib/dialyzer/test/small_SUITE_data/src/higher_order_discrepancy.erl
@@ -1,3 +1,8 @@
+%% With the patch introduced to avoid false warnings in
+%% user_SUITE_data/src/wpc_hlines.erl we can unfortunately no longer precisely
+%% catch problems like this one... The refinement procedure is still enough to
+%% keep some of the details, nevertheless.
+
 -module(higher_order_discrepancy).
 
 -export([test/1]).
diff --git a/lib/dialyzer/test/user_SUITE_data/results/wpc_hlines b/lib/dialyzer/test/user_SUITE_data/results/wpc_hlines
new file mode 100644
index 0000000..d6e3f29
--- /dev/null
+++ b/lib/dialyzer/test/user_SUITE_data/results/wpc_hlines
@@ -0,0 +1,3 @@
+
+wpc_hlines.erl:22: Function bad/1 has no local return
+wpc_hlines.erl:22: The pattern 'false' can never match the type 'true'
diff --git a/lib/dialyzer/test/user_SUITE_data/src/wpc_hlines.erl b/lib/dialyzer/test/user_SUITE_data/src/wpc_hlines.erl
new file mode 100644
index 0000000..8c205a8
--- /dev/null
+++ b/lib/dialyzer/test/user_SUITE_data/src/wpc_hlines.erl
@@ -0,0 +1,22 @@
+%% Bug reported by Dan Gudmundsson, test shrunk down by Magnus Lång.
+
+%% The problem is that dialyzer_dep generates edges from the fun 
+%% application to both of the functions, and then during the warning pass 
+%% dialyzer_dataflow:handle_apply_or_call generates warnings for any such 
+%% edge that won't return.
+
+%% Since dialyzer_dep is currently supposed to overapproximate rather than
+%% underapproximate, the fix was to modify handle_apply_or_call to not generate
+%% warnings if some of the possible funs can succeed.
+
+-module(wpc_hlines).
+
+-export([do_export/0]).
+
+do_export() ->
+   {Proj, _} =  % The culprit seems to be putting the funs in a tuple
+     {fun good/1, fun bad/1},
+   Proj(true).
+
+good(_) -> ok.
+bad(false) -> ok.
-- 
2.1.4

openSUSE Build Service is sponsored by