File 4492-dialyzer-Fix-unsound-behaviour-subtype-checks.patch of Package erlang
From 95cc79ea702f076cd1b1f2a64555fcd408132ee4 Mon Sep 17 00:00:00 2001
From: Tom Davies <todavies5@gmail.com>
Date: Thu, 25 Aug 2022 06:20:52 -0700
Subject: [PATCH] dialyzer: Fix unsound behaviour subtype checks
An invariant inside Dialyzer is that it is always safe to "simplify" a
type, (e.g. 1..1000 -> pos_integer(), or a | b | c | .. | z -> atom()).
This is safe when checking for overlap between specs and inferred types,
since the overlap never gets smaller when one of the types is grown, so
we don't make a situation where there's an overlap into one where
there's not, so we don't generate false positives.
For the case of behaviours, we use subtyping when checking the specs
and inferred types with respect to the behaviour definition. In this
case, the spec in source code may correctly be a subtype of the behaviour,
but due to internal simplifications which "should" always be safe, we can
make what was a subtype of the behaviour into something which is not,
and hence generate a false positive error about valid code.
The fix here is to switch behaviour checking to use overlap checking as
is used elsewhere in Dialyzer: it's a well tested codepath and is
consistent with the simplification logic. The drawback is that if it
weren't for the simplification logic (which is required to keep
performance reasonable), subtyping would be the correct thing to enforce,
so those cases where a spec does have an overlap with the behaviour, but
is not a subtype, will no longer be reported, since Dialyzer can't
safely tell that situation apart from valid code which has been
simplified.
We also add special casing to match the original intent, which allows
callbacks to crash (i.e. have a none() return type).
---
lib/dialyzer/src/dialyzer.erl | 12 +++----
lib/dialyzer/src/dialyzer_behaviours.erl | 34 +++++++++----------
.../results/callbacks_and_specs | 7 ++--
.../results/gen_server_incorrect_args | 2 +-
.../behaviour_SUITE_data/results/otp_6221 | 0
.../results/sample_behaviour | 4 +--
.../results/sample_behaviour_old | 2 +-
.../my_callbacks_wrong.erl | 6 ++--
.../src/otp_6221/my_behaviour.erl | 3 ++
.../src/otp_6221/my_callbacks_correct.erl | 17 ++++++++++
.../results/callbacks_and_specs | 12 +++----
.../results/sample_behaviour | 4 +--
.../my_callbacks_wrong.erl | 4 +--
.../small_SUITE_data/results/behaviour_info | 2 +-
14 files changed, 63 insertions(+), 46 deletions(-)
create mode 100644 lib/dialyzer/test/behaviour_SUITE_data/results/otp_6221
create mode 100644 lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_behaviour.erl
create mode 100644 lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_callbacks_correct.erl
diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl
index 5e3074dd61..98c684ef27 100644
--- a/lib/dialyzer/src/dialyzer.erl
+++ b/lib/dialyzer/src/dialyzer.erl
@@ -586,19 +586,19 @@ message_to_string({callback_type_mismatch, [B, F, A, ST, CT]}, I, _E) ->
" the callback of the ~w behaviour\n",
[F, A, t("("++ST++")", I), t(CT, I), B]);
message_to_string({callback_arg_type_mismatch, [B, F, A, N, ST, CT]}, I, _E) ->
- io_lib:format("The inferred type for the ~s argument of ~tw/~w (~ts) is"
- " not a supertype of ~ts, which is expected type for this"
+ io_lib:format("The inferred type for the ~s argument of ~tw/~w (~ts)"
+ " has nothing in common with ~ts, which is expected type for this"
" argument in the callback of the ~w behaviour\n",
[ordinal(N), F, A, t(ST, I), t(CT, I), B]);
message_to_string({callback_spec_type_mismatch, [B, F, A, ST, CT]}, I, _E) ->
- io_lib:format("The return type ~ts in the specification of ~tw/~w is not a"
- " subtype of ~ts, which is the expected return type for the"
+ io_lib:format("The return type ~ts in the specification of ~tw/~w has nothing"
+ " in common with ~ts, which is the expected return type for the"
" callback of the ~w behaviour\n",
[t(ST, I), F, A, t(CT, I), B]);
message_to_string({callback_spec_arg_type_mismatch, [B, F, A, N, ST, CT]},
I, _E) ->
- io_lib:format("The specified type for the ~ts argument of ~tw/~w (~ts) is"
- " not a supertype of ~ts, which is expected type for this"
+ io_lib:format("The specified type for the ~ts argument of ~tw/~w (~ts) has"
+ " nothing in common with ~ts, which is expected type for this"
" argument in the callback of the ~w behaviour\n",
[ordinal(N), F, A, t(ST, I), t(CT, I), B]);
message_to_string({callback_missing, [B, F, A]}, _I, _E) ->
diff --git a/lib/dialyzer/src/dialyzer_behaviours.erl b/lib/dialyzer/src/dialyzer_behaviours.erl
index d5c8ac0886..d3fbbcb2e1 100644
--- a/lib/dialyzer/src/dialyzer_behaviours.erl
+++ b/lib/dialyzer/src/dialyzer_behaviours.erl
@@ -126,20 +126,18 @@ check_callback(RetArgTypes, CbMFA, Behaviour, Callback,
CbReturnType = dialyzer_contracts:get_contract_return(Callback),
CbArgTypes = dialyzer_contracts:get_contract_args(Callback),
{ReturnType, ArgTypes} = RetArgTypes,
- Acc1 = case erl_types:t_is_subtype(ReturnType, CbReturnType) of
- true ->
- Acc0;
- false ->
- case erl_types:t_is_none(erl_types:t_inf(ReturnType, CbReturnType)) of
- false ->
- Acc0;
- true ->
- [{callback_type_mismatch,
- [Behaviour, Function, Arity,
- erl_types:t_to_string(ReturnType, Records),
- erl_types:t_to_string(CbReturnType, Records)]}|Acc0]
- end
- end,
+ Acc1 =
+ % Allow none() as the return type to be backwards compatible
+ % with logic that allows crashes in callbacks
+ case (not erl_types:t_is_none(ReturnType)) andalso erl_types:t_is_none(erl_types:t_inf(ReturnType, CbReturnType)) of
+ false ->
+ Acc0;
+ true ->
+ [{callback_type_mismatch,
+ [Behaviour, Function, Arity,
+ erl_types:t_to_string(ReturnType, Records),
+ erl_types:t_to_string(CbReturnType, Records)]}|Acc0]
+ end,
Acc2 = case erl_types:any_none(erl_types:t_inf_lists(ArgTypes, CbArgTypes)) of
false -> Acc1;
true ->
@@ -156,10 +154,12 @@ check_callback(RetArgTypes, CbMFA, Behaviour, Callback,
SpecArgTypes =
[erl_types:subst_all_vars_to_any(ArgT0) || ArgT0 <- SpecArgTypes0],
Acc3 =
- case erl_types:t_is_subtype(SpecReturnType, CbReturnType) of
- true ->
- Acc2;
+ % Allow none() as the return type to be backwards compatible
+ % with logic that allows crashes in callbacks
+ case (not erl_types:t_is_none(SpecReturnType)) andalso erl_types:t_is_none(erl_types:t_inf(SpecReturnType, CbReturnType)) of
false ->
+ Acc2;
+ true ->
ExtraType = erl_types:t_subtract(SpecReturnType, CbReturnType),
[{callback_spec_type_mismatch,
[File, Location, Behaviour, Function, Arity,
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/results/callbacks_and_specs b/lib/dialyzer/test/behaviour_SUITE_data/results/callbacks_and_specs
index d1bfc7295c..77ebf486c9 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/results/callbacks_and_specs
+++ b/lib/dialyzer/test/behaviour_SUITE_data/results/callbacks_and_specs
@@ -1,5 +1,6 @@
-my_callbacks_wrong.erl:26:2: The return type #state{parent::pid(),status::'closed' | 'init' | 'open',subscribe::[{pid(),integer()}],counter::integer()} in the specification of callback_init/1 is not a subtype of {'ok',_}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:26:2: The return type #state{parent::pid(),status::'closed' | 'init' | 'open',subscribe::[{pid(),integer()}],counter::integer()} in the specification of callback_init/1 has nothing in common with {'ok',_}, which is the expected return type for the callback of the my_behaviour behaviour
my_callbacks_wrong.erl:28:1: The inferred return type of callback_init/1 (#state{parent::pid(),status::'init',subscribe::[],counter::1}) has nothing in common with {'ok',_}, which is the expected return type for the callback of the my_behaviour behaviour
-my_callbacks_wrong.erl:30:2: The return type {'reply',#state{parent::pid(),status::'closed' | 'init' | 'open',subscribe::[{pid(),integer()}],counter::integer()}} in the specification of callback_cast/3 is not a subtype of {'noreply',_}, which is the expected return type for the callback of the my_behaviour behaviour
-my_callbacks_wrong.erl:39:2: The specified type for the 2nd argument of callback_call/3 (atom()) is not a supertype of pid(), which is expected type for this argument in the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:30:2: The return type {'reply',#state{parent::pid(),status::'closed' | 'init' | 'open',subscribe::[{pid(),integer()}],counter::integer()}} in the specification of callback_cast/3 has nothing in common with {'noreply',_}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:33:1: The inferred return type of callback_cast/3 ({'reply',_}) has nothing in common with {'noreply',_}, which is the expected return type for the callback of the my_behaviour behaviour
+my_callbacks_wrong.erl:39:2: The specified type for the 2nd argument of callback_call/3 (atom()) has nothing in common with pid(), which is expected type for this argument in the callback of the my_behaviour behaviour
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/results/gen_server_incorrect_args b/lib/dialyzer/test/behaviour_SUITE_data/results/gen_server_incorrect_args
index a1412f29e6..6a9aacc77e 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/results/gen_server_incorrect_args
+++ b/lib/dialyzer/test/behaviour_SUITE_data/results/gen_server_incorrect_args
@@ -2,4 +2,4 @@
gen_server_incorrect_args.erl:3:2: Undefined callback function handle_cast/2 (behaviour gen_server)
gen_server_incorrect_args.erl:3:2: Undefined callback function init/1 (behaviour gen_server)
gen_server_incorrect_args.erl:7:1: The inferred return type of handle_call/3 ({'no'} | {'ok'}) has nothing in common with {'noreply',_} | {'noreply',_,'hibernate' | 'infinity' | non_neg_integer() | {'continue',_}} | {'reply',_,_} | {'stop',_,_} | {'reply',_,_,'hibernate' | 'infinity' | non_neg_integer() | {'continue',_}} | {'stop',_,_,_}, which is the expected return type for the callback of the gen_server behaviour
-gen_server_incorrect_args.erl:7:1: The inferred type for the 2nd argument of handle_call/3 ('boo' | 'foo') is not a supertype of {pid(),gen_server:reply_tag()}, which is expected type for this argument in the callback of the gen_server behaviour
+gen_server_incorrect_args.erl:7:1: The inferred type for the 2nd argument of handle_call/3 ('boo' | 'foo') has nothing in common with {pid(),gen_server:reply_tag()}, which is expected type for this argument in the callback of the gen_server behaviour
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/results/otp_6221 b/lib/dialyzer/test/behaviour_SUITE_data/results/otp_6221
new file mode 100644
index 0000000000..e69de29bb2
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour b/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour
index ab69a698c5..347500277b 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour
+++ b/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour
@@ -3,7 +3,7 @@ sample_callback_wrong.erl:16:1: The inferred return type of sample_callback_2/0
sample_callback_wrong.erl:17:1: The inferred return type of sample_callback_3/0 ('fair') has nothing in common with 'fail' | {'ok',1..255}, which is the expected return type for the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:18:1: The inferred return type of sample_callback_4/1 ('fail') has nothing in common with 'ok', which is the expected return type for the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:20:1: The inferred return type of sample_callback_5/1 (string()) has nothing in common with 'fail' | 'ok', which is the expected return type for the callback of the sample_behaviour behaviour
-sample_callback_wrong.erl:20:1: The inferred type for the 1st argument of sample_callback_5/1 (atom()) is not a supertype of 1..255, which is expected type for this argument in the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:20:1: The inferred type for the 1st argument of sample_callback_5/1 (atom()) has nothing in common with 1..255, which is expected type for this argument in the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:22:1: The inferred return type of sample_callback_6/3 ({'okk',number()}) has nothing in common with 'fail' | {'ok',1..255}, which is the expected return type for the callback of the sample_behaviour behaviour
-sample_callback_wrong.erl:22:1: The inferred type for the 3rd argument of sample_callback_6/3 (atom()) is not a supertype of string(), which is expected type for this argument in the callback of the sample_behaviour behaviour
+sample_callback_wrong.erl:22:1: The inferred type for the 3rd argument of sample_callback_6/3 (atom()) has nothing in common with string(), which is expected type for this argument in the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:4:2: Undefined callback function sample_callback_1/0 (behaviour sample_behaviour)
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour_old b/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour_old
index 6d8145a8ca..5f2b8d2ad4 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour_old
+++ b/lib/dialyzer/test/behaviour_SUITE_data/results/sample_behaviour_old
@@ -1,4 +1,4 @@
-incorrect_args_callback.erl:12:1: The inferred type for the 2nd argument of bar/2 ('yes') is not a supertype of [any()], which is expected type for this argument in the callback of the correct_behaviour behaviour
+incorrect_args_callback.erl:12:1: The inferred type for the 2nd argument of bar/2 ('yes') has nothing in common with [any()], which is expected type for this argument in the callback of the correct_behaviour behaviour
incorrect_return_callback.erl:9:1: The inferred return type of foo/0 ('error') has nothing in common with 'no' | 'yes', which is the expected return type for the callback of the correct_behaviour behaviour
missing_callback.erl:5:2: Undefined callback function foo/0 (behaviour correct_behaviour)
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl b/lib/dialyzer/test/behaviour_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
index 0459622dc1..0f485096ff 100644
--- a/lib/dialyzer/test/behaviour_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
+++ b/lib/dialyzer/test/behaviour_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
@@ -28,13 +28,13 @@
callback_init(Parent) -> #state{parent = Parent}. %% Wrong return
-spec callback_cast(state(), pid() | atom(), cast_message()) ->
- {'noreply' | 'reply', state()}. %% More generic spec
+ {'reply', state()}. %% Non-overlapping spec
callback_cast(#state{parent = Pid} = State, Pid, Message)
when Message =:= 'open'; Message =:= 'close' ->
- {noreply, State#state{status = Message}};
+ {reply, State#state{status = Message}};
callback_cast(State, _Pid, _Message) ->
- {noreply, State}.
+ {reply, State}.
-spec callback_call(state(), atom(), call_message()) -> %% Wrong arg spec
{'reply', state(), call_reply()}.
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_behaviour.erl b/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_behaviour.erl
new file mode 100644
index 0000000000..347ea403c2
--- /dev/null
+++ b/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_behaviour.erl
@@ -0,0 +1,3 @@
+-module(my_behaviour).
+
+-callback foo() -> #{ {{{f,f}, f}, f} => x }.
diff --git a/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_callbacks_correct.erl b/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_callbacks_correct.erl
new file mode 100644
index 0000000000..4a08017c84
--- /dev/null
+++ b/lib/dialyzer/test/behaviour_SUITE_data/src/otp_6221/my_callbacks_correct.erl
@@ -0,0 +1,17 @@
+-module(my_callbacks_correct).
+
+-behaviour(my_behaviour).
+
+-export([foo/0]).
+
+-type pair(A,B) :: {A,B}.
+
+-type nested() :: pair(pair(pair(f,f),f),f).
+
+%% This is correctly implemented, but a combination of Dialyzer
+%% "simplification" logic and subtyping rules for behaviours means
+%% this implementation has historically been erroneously rejected
+-spec foo() -> #{ nested() => x }.
+foo() ->
+ Ret = #{ {{{f,f}, f}, f} => x },
+ Ret.
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs b/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
index 0d513775a1..6e34494e2a 100644
--- a/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
+++ b/lib/dialyzer/test/indent_SUITE_data/results/callbacks_and_specs
@@ -3,7 +3,7 @@ my_callbacks_wrong.erl:26:2: The return type
#state{parent :: pid(),
status :: 'closed' | 'init' | 'open',
subscribe :: [{pid(), integer()}],
- counter :: integer()} in the specification of callback_init/1 is not a subtype of
+ counter :: integer()} in the specification of callback_init/1 has nothing in common with
{'ok', _}, which is the expected return type for the callback of the my_behaviour behaviour
my_callbacks_wrong.erl:28:1: The inferred return type of callback_init/1
(#state{parent :: pid(),
@@ -11,13 +11,9 @@ my_callbacks_wrong.erl:28:1: The inferred return type of callback_init/1
subscribe :: [],
counter :: 1}) has nothing in common with
{'ok', _}, which is the expected return type for the callback of the my_behaviour behaviour
-my_callbacks_wrong.erl:30:2: The return type
- {'reply',
- #state{parent :: pid(),
- status :: 'closed' | 'init' | 'open',
- subscribe :: [{pid(), integer()}],
- counter :: integer()}} in the specification of callback_cast/3 is not a subtype of
+my_callbacks_wrong.erl:33:1: The inferred return type of callback_cast/3
+ ({'reply', _}) has nothing in common with
{'noreply', _}, which is the expected return type for the callback of the my_behaviour behaviour
my_callbacks_wrong.erl:39:2: The specified type for the 2nd argument of callback_call/3 (
- atom()) is not a supertype of
+ atom()) has nothing in common with
pid(), which is expected type for this argument in the callback of the my_behaviour behaviour
diff --git a/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour b/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
index e7ae7505f6..393d428576 100644
--- a/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
+++ b/lib/dialyzer/test/indent_SUITE_data/results/sample_behaviour
@@ -12,12 +12,12 @@ sample_callback_wrong.erl:20:1: The inferred return type of sample_callback_5/1
(string()) has nothing in common with
'fail' | 'ok', which is the expected return type for the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:20:1: The inferred type for the 1st argument of sample_callback_5/1 (
- atom()) is not a supertype of
+ atom()) has nothing in common with
1..255, which is expected type for this argument in the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:22:1: The inferred return type of sample_callback_6/3
({'okk', number()}) has nothing in common with
'fail' | {'ok', 1..255}, which is the expected return type for the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:22:1: The inferred type for the 3rd argument of sample_callback_6/3 (
- atom()) is not a supertype of
+ atom()) has nothing in common with
string(), which is expected type for this argument in the callback of the sample_behaviour behaviour
sample_callback_wrong.erl:4:2: Undefined callback function sample_callback_1/0 (behaviour sample_behaviour)
diff --git a/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
index 0459622dc1..31613ca06f 100644
--- a/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
+++ b/lib/dialyzer/test/indent_SUITE_data/src/callbacks_and_specs/my_callbacks_wrong.erl
@@ -32,9 +32,9 @@ callback_init(Parent) -> #state{parent = Parent}. %% Wrong return
callback_cast(#state{parent = Pid} = State, Pid, Message)
when Message =:= 'open'; Message =:= 'close' ->
- {noreply, State#state{status = Message}};
+ {reply, State#state{status = Message}}; % Wrong return
callback_cast(State, _Pid, _Message) ->
- {noreply, State}.
+ {reply, State}. % Wrong return
-spec callback_call(state(), atom(), call_message()) -> %% Wrong arg spec
{'reply', state(), call_reply()}.
diff --git a/lib/dialyzer/test/small_SUITE_data/results/behaviour_info b/lib/dialyzer/test/small_SUITE_data/results/behaviour_info
index 6497ddae80..ea17933586 100644
--- a/lib/dialyzer/test/small_SUITE_data/results/behaviour_info
+++ b/lib/dialyzer/test/small_SUITE_data/results/behaviour_info
@@ -1,2 +1,2 @@
-with_bad_format_status.erl:12:1: The inferred type for the 1st argument of format_status/2 ('bad_arg') is not a supertype of 'normal' | 'terminate', which is expected type for this argument in the callback of the gen_server behaviour
+with_bad_format_status.erl:12:1: The inferred type for the 1st argument of format_status/2 ('bad_arg') has nothing in common with 'normal' | 'terminate', which is expected type for this argument in the callback of the gen_server behaviour
--
2.35.3