Skip to content

Commit

Permalink
dialyzer: fix issues related to opaques
Browse files Browse the repository at this point in the history
Fix #9140.
  • Loading branch information
lucioleKi committed Dec 4, 2024
1 parent 511e33b commit 7382eab
Show file tree
Hide file tree
Showing 6 changed files with 31 additions and 7 deletions.
2 changes: 2 additions & 0 deletions lib/dialyzer/src/dialyzer.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@
-define(WARN_CONTRACT_EXTRA_RETURN, warn_contract_extra_return).
-define(WARN_CONTRACT_MISSING_RETURN, warn_contract_missing_return).
-define(WARN_CONTRACT_NOT_EQUAL, warn_contract_not_equal).
-define(WARN_CONTRACT_OPAQUE, warn_contract_opaque).
-define(WARN_CONTRACT_RANGE, warn_contract_range).
-define(WARN_CONTRACT_SUBTYPE, warn_contract_subtype).
-define(WARN_CONTRACT_SUPERTYPE, warn_contract_supertype).
Expand Down Expand Up @@ -67,6 +68,7 @@
-type dial_warn_tag() :: ?WARN_BEHAVIOUR | ?WARN_BIN_CONSTRUCTION
| ?WARN_CALLGRAPH | ?WARN_CONTRACT_EXTRA_RETURN
| ?WARN_CONTRACT_MISSING_RETURN | ?WARN_CONTRACT_NOT_EQUAL
| ?WARN_CONTRACT_OPAQUE
| ?WARN_CONTRACT_RANGE | ?WARN_CONTRACT_SUBTYPE
| ?WARN_CONTRACT_SUPERTYPE | ?WARN_CONTRACT_SYNTAX
| ?WARN_CONTRACT_TYPES | ?WARN_FAILING_CALL
Expand Down
2 changes: 1 addition & 1 deletion lib/dialyzer/src/dialyzer_contracts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -905,7 +905,7 @@ invalid_contract_warning({M, F, A}, WarningInfo, ProblemDetails, Contract, SuccT
contract_opaque_warning({M, F, A}, WarningInfo, OpType, SuccType, RecDict) ->
OpaqueStr = erl_types:t_to_string(OpType),
SuccTypeStr = dialyzer_utils:format_sig(SuccType, RecDict),
{?WARN_CONTRACT_TYPES, WarningInfo,
{?WARN_CONTRACT_OPAQUE, WarningInfo,
{contract_with_opaque, [M, F, A, OpaqueStr, SuccTypeStr]}}.

overlapping_contract_warning({M, F, A}, WarningInfo) ->
Expand Down
4 changes: 2 additions & 2 deletions lib/dialyzer/src/dialyzer_dataflow.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1760,13 +1760,13 @@ bind_guard(Guard, Map, Env, Eval, State0) ->
values ->
Es = cerl:values_es(Guard),
{Types, State1} = lists:mapfoldl(fun(V, StateAcc0) ->
{_, Type, StateAcc0} =
{_, Type, StateAcc} =
bind_guard(V,
Map,
Env,
dont_know,
StateAcc0),
{Type, StateAcc0}
{Type, StateAcc}
end, State0, Es),
{Map, t_product(Types), State1};
var ->
Expand Down
12 changes: 8 additions & 4 deletions lib/dialyzer/src/dialyzer_options.erl
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@ build(Opts) ->
?WARN_FAILING_CALL,
?WARN_BIN_CONSTRUCTION,
?WARN_MAP_CONSTRUCTION,
?WARN_CONTRACT_OPAQUE,
?WARN_CONTRACT_RANGE,
?WARN_CONTRACT_TYPES,
?WARN_CONTRACT_SYNTAX,
Expand Down Expand Up @@ -502,15 +503,18 @@ build_warnings([Opt|Opts], Warnings) ->
no_match ->
ordsets:del_element(?WARN_MATCHING, Warnings);
no_opaque ->
S = ordsets:from_list([?WARN_OPAQUE,
S = ordsets:from_list([?WARN_CONTRACT_OPAQUE,
?WARN_OPAQUE,
?WARN_OPAQUE_UNION]),
ordsets:subtract(Warnings, S);
no_fail_call ->
ordsets:del_element(?WARN_FAILING_CALL, Warnings);
no_contracts ->
Warnings1 = ordsets:del_element(?WARN_CONTRACT_SYNTAX, Warnings),
Warnings2 = ordsets:del_element(?WARN_OVERLAPPING_CONTRACT, Warnings1),
ordsets:del_element(?WARN_CONTRACT_TYPES, Warnings2);
S = ordsets:from_list([?WARN_CONTRACT_OPAQUE,
?WARN_CONTRACT_SYNTAX,
?WARN_CONTRACT_TYPES,
?WARN_OVERLAPPING_CONTRACT]),
ordsets:subtract(Warnings, S);
no_behaviours ->
ordsets:del_element(?WARN_BEHAVIOUR, Warnings);
no_undefined_callbacks ->
Expand Down
9 changes: 9 additions & 0 deletions lib/dialyzer/test/opaque_SUITE_data/src/para/para6.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
-module(para6).
-dialyzer({no_opaque,[exp_adt/0]}).

-type exp() :: para3_adt:exp1(para3_adt:exp2()).

-spec exp_adt() -> exp(). % invalid type spec

exp_adt() ->
3.
9 changes: 9 additions & 0 deletions lib/dialyzer/test/opaque_SUITE_data/src/para/para7.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
-module(para6).
-dialyzer({no_contracts, exp_adt/0}).

-type exp() :: para3_adt:exp1(para3_adt:exp2()).

-spec exp_adt() -> exp(). % invalid type spec

exp_adt() ->
3.

0 comments on commit 7382eab

Please sign in to comment.