Skip to content

Commit

Permalink
Merge pull request #9218 from jhogberg/john/dialyzer/fix-silly-crash/G…
Browse files Browse the repository at this point in the history
…H-9200/GH-9199

Fix a few minor issues in dialyzer
  • Loading branch information
jhogberg authored Jan 9, 2025
2 parents 42c5123 + b9d542d commit 1878f14
Show file tree
Hide file tree
Showing 5 changed files with 71 additions and 5 deletions.
3 changes: 1 addition & 2 deletions lib/dialyzer/src/dialyzer_contracts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -320,8 +320,7 @@ locate_invalid_elems([Contract], SuccType) ->
SRange = erl_types:t_fun_range(SuccType),

ProblematicArgs =
[erl_types:t_is_none(erl_types:t_inf(Cont, Succ)) andalso
(not erl_types:t_is_none(Cont)) ||
[erl_types:t_is_none(erl_types:t_inf(Cont, Succ)) ||
Cont <- CArgs && Succ <- SArgs],

ProblematicRange =
Expand Down
6 changes: 3 additions & 3 deletions lib/dialyzer/src/erl_types.erl
Original file line number Diff line number Diff line change
Expand Up @@ -4632,9 +4632,9 @@ check_fields(RecName, [{type, _, field_type, [{atom, _, Name}, Abstr]}|Left],
{Type, C1} = t_from_form(Abstr, ET, Site, MR, V, C),
{Name, _, DeclType} = lists:keyfind(Name, 1, DeclFields),
TypeNoVars = subst_all_vars_to_any(Type),
case t_is_subtype(TypeNoVars, DeclType) of
false -> {error, Name};
true -> check_fields(RecName, Left, DeclFields, S, C1)
case t_is_impossible(t_inf(TypeNoVars, DeclType)) of
true -> {error, Name};
false -> check_fields(RecName, Left, DeclFields, S, C1)
end;
check_fields(_RecName, [], _Decl, _S, C) ->
C.
Expand Down
27 changes: 27 additions & 0 deletions lib/dialyzer/test/small_SUITE_data/results/contract6
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@

contract6.erl:28:2: Invalid type specification for function contract6:swap/1.
The success typing is contract6:swap(_) -> none()
But the spec is contract6:swap(#r{}) -> #r{}
They do not overlap in the 1st argument
contract6.erl:29:1: Function swap/1 has no local return
contract6.erl:29:1: Matching of pattern {'r', T1, T2} tagged with a record name violates the declared type of any()

%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2024. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%% %CopyrightEnd%
%%
30 changes: 30 additions & 0 deletions lib/dialyzer/test/small_SUITE_data/src/contract6.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2024. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
%% You may obtain a copy of the License at
%%
%% http://www.apache.org/licenses/LICENSE-2.0
%%
%% Unless required by applicable law or agreed to in writing, software
%% distributed under the License is distributed on an "AS IS" BASIS,
%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
%% See the License for the specific language governing permissions and
%% limitations under the License.
%%
%% %CopyrightEnd%
%%

-module(contract6).
-export([swap/1]).
-nominal t1() :: none().
-nominal t2() :: none().

-record(r, {t1 :: t1(), t2 :: t2()}).

-spec swap(#r{}) -> #r{}.
swap(#r{t1 = T1, t2 = T2}) ->
#r{t1 = T2, t2 = T1}.
10 changes: 10 additions & 0 deletions lib/dialyzer/test/small_SUITE_data/src/contracts_with_subtypes.erl
Original file line number Diff line number Diff line change
Expand Up @@ -298,3 +298,13 @@ factored_ets_new_t() ->
factored_ets_new(name,{bag}),
factored_ets_new(name,bag),
ok.

%===============================================================================

-nominal t1() :: t2().
-nominal t2() :: integer().
-record(r, {t :: t1()}).

-spec swap_r(#r{}) -> #r{t :: t2()}.
swap_r(#r{t = T}) ->
#r{t = T}.

0 comments on commit 1878f14

Please sign in to comment.