Skip to content

Commit

Permalink
erl_types: Be less strict about subtyping in record field checks
Browse files Browse the repository at this point in the history
  • Loading branch information
jhogberg committed Dec 19, 2024
1 parent 0b71469 commit b9d542d
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 3 deletions.
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
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 b9d542d

Please sign in to comment.