File 0817-dialyzer-Fix-an-overloaded-contract-warning.patch of Package erlang

From e25ed9ca25cae5dccb44f0f2204eb795c31c291e Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 12 Nov 2019 16:10:43 +0100
Subject: [PATCH 1/2] dialyzer: Fix an overloaded contract warning

When creating the missing_range warning, the supremum of all function
type ranges is considered, not the range of one function type at a
time.

Notice that more extra_range messages than before can be emitted (the
check for extra_range was not always performed if a missing_range was
found).
---
 lib/dialyzer/src/dialyzer_contracts.erl            | 36 +++++++++++----------
 .../test/specdiffs_SUITE_data/results/overloaded   |  6 ++++
 .../test/specdiffs_SUITE_data/src/overloaded.erl   | 37 ++++++++++++++++++++++
 3 files changed, 63 insertions(+), 16 deletions(-)
 create mode 100644 lib/dialyzer/test/specdiffs_SUITE_data/results/overloaded
 create mode 100644 lib/dialyzer/test/specdiffs_SUITE_data/src/overloaded.erl

diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl
index 17b2168852..e041c43cc1 100644
--- a/lib/dialyzer/src/dialyzer_contracts.erl
+++ b/lib/dialyzer/src/dialyzer_contracts.erl
@@ -248,7 +248,19 @@ check_contract(#contract{contracts = Contracts}, SuccType, Opaques) ->
 		   || Contract <- Contracts2],
 	case check_contract_inf_list(InfList, SuccType, Opaques) of
 	  {error, _} = Invalid -> Invalid;
-	  ok -> check_extraneous(Contracts2, SuccType)
+          ok ->
+            case check_extraneous(Contracts2, SuccType) of
+              {error, invalid_contract} = Err ->
+                Err;
+              {error, {extra_range, _, _}} = Err ->
+                MissingError = check_missing(Contracts2, SuccType),
+                {range_warnings, [Err | MissingError]};
+              ok ->
+                case check_missing(Contracts2, SuccType) of
+                  [] -> ok;
+                  ErrorL -> {range_warnings, ErrorL}
+                end
+            end
 	end
     end
   catch
@@ -304,15 +316,8 @@ check_contract_inf_list([], _SuccType, _Opaques, OM) ->
 check_extraneous([], _SuccType) -> ok;
 check_extraneous([C|Cs], SuccType) ->
   case check_extraneous_1(C, SuccType) of
-    {error, invalid_contract} = Error ->
-      Error;
-    {error, {extra_range, _, _}} = Error ->
-      {range_warnings, [Error | check_missing(C, SuccType)]};
-    ok ->
-      case check_missing(C, SuccType) of
-        [] -> check_extraneous(Cs, SuccType);
-        ErrorL -> {range_warnings, ErrorL}
-      end
+    {error, _} = Error -> Error;
+    ok -> check_extraneous(Cs, SuccType)
   end.
 
 check_extraneous_1(Contract, SuccType) ->
@@ -363,16 +368,15 @@ map_part(Type) ->
 is_empty_map(Type) ->
   erl_types:t_is_equal(Type, erl_types:t_from_term(#{})).
 
-check_missing(Contract, SuccType) ->
-  CRng = erl_types:t_fun_range(Contract),
+check_missing(Contracts, SuccType) ->
+  CRanges = [erl_types:t_fun_range(C) || C <- Contracts],
+  AllCRange = erl_types:t_sup(CRanges),
   STRng = erl_types:t_fun_range(SuccType),
   STRngs = erl_types:t_elements(STRng),
-  ?debug("\nCR = ~ts\nSR = ~ts\n", [erl_types:t_to_string(CRng),
-                                    erl_types:t_to_string(STRng)]),
   case [STR || STR <- STRngs,
-              erl_types:t_is_none(erl_types:t_inf(STR, CRng))] of
+              erl_types:t_is_none(erl_types:t_inf(STR, AllCRange))] of
     [] -> [];
-    STRs -> [{error, {missing_range, erl_types:t_sup(STRs), CRng}}]
+    STRs -> [{error, {missing_range, erl_types:t_sup(STRs), AllCRange}}]
   end.
 
 %% This is the heart of the "range function"
diff --git a/lib/dialyzer/test/specdiffs_SUITE_data/results/overloaded b/lib/dialyzer/test/specdiffs_SUITE_data/results/overloaded
new file mode 100644
index 0000000000..f68917c009
--- /dev/null
+++ b/lib/dialyzer/test/specdiffs_SUITE_data/results/overloaded
@@ -0,0 +1,6 @@
+
+overloaded.erl:12: Type specification overloaded:u('a' | 'b' | 'c') -> term() is a subtype of the success typing: overloaded:u(_) -> any()
+overloaded.erl:17: The success typing for overloaded:v/1 implies that the function might also return {'ok','term'} but the specification return is 'ok'
+overloaded.erl:22: Type specification overloaded:x(_) -> {'ok','term'} | 'ok' is a supertype of the success typing: overloaded:x('a' | 'b') -> 'ok' | {'ok','term'}
+overloaded.erl:29: The success typing for overloaded:over/1 implies that the function might also return 'ffyy3' but the specification return is 'ffyy1' | {'ffyy2',integer()}
+overloaded.erl:7: Type specification overloaded:t('a' | 'b') -> term() is a subtype of the success typing: overloaded:t('a' | 'b' | 'c') -> any()
diff --git a/lib/dialyzer/test/specdiffs_SUITE_data/src/overloaded.erl b/lib/dialyzer/test/specdiffs_SUITE_data/src/overloaded.erl
new file mode 100644
index 0000000000..67757fbb2a
--- /dev/null
+++ b/lib/dialyzer/test/specdiffs_SUITE_data/src/overloaded.erl
@@ -0,0 +1,37 @@
+-module(overloaded).
+
+-export([t/1, v/1]).
+
+-export([over/1]).
+
+-spec t(a | b) -> term().
+
+t(A) ->
+    u(A).
+
+-spec u(a | b | c) -> term().
+
+u(X) ->
+    X.
+
+-spec v(_) -> ok.
+
+v(A) ->
+    x(A).
+
+-spec x(_) -> {ok, term} | ok.
+
+x(a) ->
+    {ok, term};
+x(b) ->
+    ok.
+
+-spec over(A) -> ffyy1 when A :: a | b;
+          (B) -> {ffyy2, integer()} when B :: c | d.
+
+over(a) ->
+    ffyy1;
+over(c) ->
+    {ffyy2, 1};
+over(d) ->
+    ffyy3.
-- 
2.16.4

openSUSE Build Service is sponsored by