Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
4201-dialyzer-Improve-error-messages-for-invali...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 4201-dialyzer-Improve-error-messages-for-invalid-specs.patch of Package erlang
From 2f8efcd24891140809217f1539ccf1a4f098e723 Mon Sep 17 00:00:00 2001 From: Tom Davies <todavies5@gmail.com> Date: Fri, 26 Aug 2022 05:36:21 -0700 Subject: [PATCH] dialyzer: Improve error messages for invalid specs Invalid spec messages now include the spec side-by-side with the inferred type, and explicitly call out which arguments don't overlap, and whether the return types don't overlap. --- lib/dialyzer/src/dialyzer.erl | 34 ++++++++++- lib/dialyzer/src/dialyzer_contracts.erl | 58 +++++++++++++------ lib/dialyzer/test/cplt_SUITE.erl | 8 +-- lib/dialyzer/test/dialyzer_common.erl | 8 +-- lib/dialyzer/test/incremental_SUITE.erl | 2 +- .../results/contracts_with_subtypes | 12 +++- .../indent_SUITE_data/results/record_update | 6 +- .../test/indent_SUITE_data/results/simple | 24 ++++++-- lib/dialyzer/test/iplt_SUITE.erl | 8 +-- .../map_SUITE_data/results/contract_violation | 5 +- .../test/map_SUITE_data/results/opaque_key | 25 ++++++-- .../test/opaque_SUITE_data/results/int | 10 +++- .../results/multiple_wrong_opaques | 5 +- .../test/opaque_SUITE_data/results/para | 15 ++++- .../test/opaque_SUITE_data/results/simple | 20 +++++-- .../small_SUITE_data/results/binary_nonempty | 35 ++++++++--- .../small_SUITE_data/results/binary_redef2 | 10 +++- .../test/small_SUITE_data/results/chars | 5 +- .../test/small_SUITE_data/results/contract5 | 5 +- .../results/contracts_with_subtypes | 10 +++- .../results/empty_list_infimum | 5 +- .../small_SUITE_data/results/invalid_spec_2 | 5 +- .../small_SUITE_data/results/invalid_specs | 5 +- .../test/small_SUITE_data/results/maps_sum | 5 +- .../test/small_SUITE_data/results/predef | 35 ++++++++--- .../small_SUITE_data/results/record_update | 5 +- .../small_SUITE_data/results/tuple_set_crash | 30 ++++++++-- .../test/small_SUITE_data/results/types_arity | 5 +- 28 files changed, 312 insertions(+), 88 deletions(-) diff --git a/lib/dialyzer/src/dialyzer.erl b/lib/dialyzer/src/dialyzer.erl index 5e3074dd61..2da40d6885 100644 --- a/lib/dialyzer/src/dialyzer.erl +++ b/lib/dialyzer/src/dialyzer.erl @@ -516,9 +516,16 @@ message_to_string({contract_range, [Contract, M, F, ArgStrings, " return for ~tw~ts on position ~s is ~ts\n", [con(M, F, Contract, I), F, a(ArgStrings, I), pos(Location, E), t(CRet, I)]); -message_to_string({invalid_contract, [M, F, A, Sig]}, I, _E) -> - io_lib:format("Invalid type specification for function ~w:~tw/~w." - " The success typing is ~ts\n", [M, F, A, sig(Sig, I)]); +message_to_string({invalid_contract, [M, F, A, none, Contract, Sig]}, I, _E) -> + io_lib:format("Invalid type specification for function ~w:~tw/~w.\n" + " The success typing is ~ts\n" + " But the spec is ~ts\n", [M, F, A, con(M, F, Sig, I), con(M, F, Contract, I)]); +message_to_string({invalid_contract, [M, F, A, InvalidContractDetails, Contract, Sig]}, I, _E) -> + io_lib:format("Invalid type specification for function ~w:~tw/~w.\n" + " The success typing is ~ts\n" + " But the spec is ~ts\n" + "~ts", + [M, F, A, con(M, F, Sig, I), con(M, F, Contract, I), format_invalid_contract_details(InvalidContractDetails)]); message_to_string({contract_with_opaque, [M, F, A, OpaqueType, SigType]}, I, _E) -> io_lib:format("The specification for ~w:~tw/~w" @@ -621,6 +628,27 @@ message_to_string({unknown_behaviour, B}, _I, _E) -> %% Auxiliary functions below %%----------------------------------------------------------------------------- +format_invalid_contract_details({InvalidArgIdxs, IsRangeInvalid}) -> + ArgOrd = form_position_string(InvalidArgIdxs), + ArgDesc = + case InvalidArgIdxs of + [] -> ""; + [_] -> io_lib:format("They do not overlap in the ~ts argument", [ArgOrd]); + [_|_] -> io_lib:format("They do not overlap in the ~ts arguments", [ArgOrd]) + end, + RangeDesc = + case IsRangeInvalid of + true -> "return types do not overlap"; + false -> "" + end, + case {ArgDesc, RangeDesc} of + {"", ""} -> ""; + {"", [_|_]} -> io_lib:format(" The ~ts\n", [RangeDesc]); + {[_|_], ""} -> io_lib:format(" ~ts\n", [ArgDesc]); + {[_|_], [_|_]} -> io_lib:format(" ~ts, and the ~ts\n", [ArgDesc, RangeDesc]) + end. + + call_or_apply_to_string(ArgNs, FailReason, SigArgs, SigRet, {IsOverloaded, Contract}, I) -> PositionString = form_position_string(ArgNs), diff --git a/lib/dialyzer/src/dialyzer_contracts.erl b/lib/dialyzer/src/dialyzer_contracts.erl index 22c27e318a..043a99560f 100644 --- a/lib/dialyzer/src/dialyzer_contracts.erl +++ b/lib/dialyzer/src/dialyzer_contracts.erl @@ -269,6 +269,7 @@ check_contracts(Contracts, Callgraph, FunTypes, ModOpaques) -> 'ok' | {'error', 'invalid_contract' + | {'invalid_contract', {InvalidArgIdxs :: [pos_integer()], IsReturnTypeInvalid :: boolean()}} | {'opaque_mismatch', erl_types:erl_type()} | {'overlapping_contract', [module() | atom() | byte()]} | string()} @@ -299,12 +300,11 @@ check_contract(#contract{contracts = Contracts}, SuccType, Opaques) -> ok -> InfList = [{Contract, erl_types:t_inf(Contract, SuccType, Opaques)} || Contract <- Contracts2], - case check_contract_inf_list(InfList, SuccType, Opaques) of - {error, _} = Invalid -> Invalid; + case check_contract_inf_list(InfList, SuccType, Opaques) of + {error, _} = Invalid -> Invalid; ok -> case check_extraneous(Contracts2, SuccType, Opaques) of - {error, invalid_contract} = Err -> - Err; + {error, {invalid_contract, _}} = Err -> Err; {error, {extra_range, _, _}} = Err -> MissingError = check_missing(Contracts2, SuccType, Opaques), {range_warnings, [Err | MissingError]}; @@ -320,6 +320,25 @@ check_contract(#contract{contracts = Contracts}, SuccType, Opaques) -> throw:{error, _} = Error -> Error end. +locate_invalid_elems(InfList) -> + case InfList of + [{Contract, Inf}] -> + ArgComparisons = lists:zip(erl_types:t_fun_args(Contract), + erl_types:t_fun_args(Inf)), + ProblematicArgs = + [erl_types:t_is_none(Succ) andalso (not erl_types:t_is_none(Cont)) + || {Cont,Succ} <- ArgComparisons], + ProblematicRange = + erl_types:t_is_none(erl_types:t_fun_range(Inf)) + andalso (not erl_types:t_is_none(erl_types:t_fun_range(Contract))), + ProblematicArgIdxs = [Idx || + {Idx, IsProblematic} <- + lists:enumerate(ProblematicArgs), IsProblematic], + {error, {invalid_contract, {ProblematicArgIdxs, ProblematicRange}}}; + _ -> + {error, invalid_contract} + end. + check_domains([_]) -> ok; check_domains([Dom|Doms]) -> Fun = fun(D) -> @@ -330,16 +349,19 @@ check_domains([Dom|Doms]) -> false -> error end. + %% Allow a contract if one of the overloaded contracts is possible. %% We used to be more strict, e.g., all overloaded contracts had to be %% possible. check_contract_inf_list(List, SuccType, Opaques) -> case check_contract_inf_list(List, SuccType, Opaques, []) of ok -> ok; - {error, []} -> {error, invalid_contract}; + {error, []} -> + locate_invalid_elems(List); {error, [{SigRange, ContrRange}|_]} -> case erl_types:t_find_opaque_mismatch(SigRange, ContrRange, Opaques) of - error -> {error, invalid_contract}; + error -> + locate_invalid_elems(List); {ok, _T1, T2} -> {error, {opaque_mismatch, T2}} end end. @@ -383,13 +405,12 @@ check_extraneous_1(Contract, SuccType, Opaques) -> case [CR || CR <- CRngs, erl_types:t_is_none(erl_types:t_inf(CR, STRng, Opaques))] of [] -> - case bad_extraneous_list(CRng, STRng) - orelse bad_extraneous_map(CRng, STRng) - of - true -> {error, invalid_contract}; - false -> ok + case bad_extraneous_list(CRng, STRng) orelse bad_extraneous_map(CRng, STRng) of + true -> {error, {invalid_contract, {[],true}}}; + false -> ok end; - CRs -> {error, {extra_range, erl_types:t_sup(CRs), STRng}} + CRs -> + {error, {extra_range, erl_types:t_sup(CRs), STRng}} end. bad_extraneous_list(CRng, STRng) -> @@ -819,7 +840,9 @@ get_invalid_contract_warnings_funs([{MFA, {FileLocation, Contract, _Xtra}}|Left] NewAcc = case check_contract(Contract, Sig, Opaques) of {error, invalid_contract} -> - [invalid_contract_warning(MFA, WarningInfo, Sig, RecDict)|Acc]; + [invalid_contract_warning(MFA, WarningInfo, none, Contract, Sig, RecDict)|Acc]; + {error, {invalid_contract, {_ProblematicArgIdxs, _IsRangeProblematic} = ProblemDetails}} -> + [invalid_contract_warning(MFA, WarningInfo, ProblemDetails, Contract, Sig, RecDict)|Acc]; {error, {opaque_mismatch, T2}} -> W = contract_opaque_warning(MFA, WarningInfo, T2, Sig, RecDict), [W|Acc]; @@ -864,7 +887,7 @@ get_invalid_contract_warnings_funs([{MFA, {FileLocation, Contract, _Xtra}}|Left] BifSig = erl_types:t_fun(BifArgs, BifRet), case check_contract(Contract, BifSig, Opaques) of {error, _} -> - [invalid_contract_warning(MFA, WarningInfo, BifSig, RecDict) + [invalid_contract_warning(MFA, WarningInfo, none, Contract, BifSig, RecDict) |Acc]; {range_warnings, _} -> picky_contract_check(CSig, BifSig, MFA, WarningInfo, @@ -883,9 +906,10 @@ get_invalid_contract_warnings_funs([{MFA, {FileLocation, Contract, _Xtra}}|Left] get_invalid_contract_warnings_funs([], _Plt, _RecDict, _Opaques, Acc) -> Acc. -invalid_contract_warning({M, F, A}, WarningInfo, SuccType, RecDict) -> - SuccTypeStr = dialyzer_utils:format_sig(SuccType, RecDict), - {?WARN_CONTRACT_TYPES, WarningInfo, {invalid_contract, [M, F, A, SuccTypeStr]}}. +invalid_contract_warning({M, F, A}, WarningInfo, ProblemDetails, Contract, SuccType, RecDict) -> + SuccTypeStr = lists:flatten(dialyzer_utils:format_sig(SuccType, RecDict)), + ContractTypeStr = contract_to_string(Contract), + {?WARN_CONTRACT_TYPES, WarningInfo, {invalid_contract, [M, F, A, ProblemDetails, ContractTypeStr, SuccTypeStr]}}. contract_opaque_warning({M, F, A}, WarningInfo, OpType, SuccType, RecDict) -> OpaqueStr = erl_types:t_to_string(OpType), diff --git a/lib/dialyzer/test/dialyzer_common.erl b/lib/dialyzer/test/dialyzer_common.erl index 2ef3e69daa..f7c00e3389 100644 --- a/lib/dialyzer/test/dialyzer_common.erl +++ b/lib/dialyzer/test/dialyzer_common.erl @@ -120,7 +120,7 @@ build_plt(PltFilename) -> end. -spec check(atom(), dialyzer:dial_options(), string(), string()) -> - 'same' | {differ, [term()]}. + 'same' | {differ, TestCase :: atom(), [term()]}. check(TestCase, Opts, Dir, OutDir) -> PltFilename = plt_file(OutDir), @@ -161,7 +161,7 @@ check(TestCase, Opts, Dir, OutDir) -> case file_utils:diff(NewResFile, OldResFile) of 'same' -> file:delete(NewResFile), 'same'; - Any -> escape_strings(Any) + {'differ', List} -> escape_strings({'differ', TestCase, List}) end catch Kind:Error -> {'dialyzer crashed', Kind, Error} @@ -203,9 +203,9 @@ create_all_suites() -> Suites = get_suites(Cwd), lists:foreach(fun create_suite/1, Suites). -escape_strings({differ,List}) -> +escape_strings({differ, TestCase, List}) -> Map = fun({T,L,S}) -> {T,L,xmerl_lib:export_text(S)} end, - {differ, lists:keysort(3, lists:map(Map, List))}. + {differ, TestCase, lists:keysort(3, lists:map(Map, List))}. -spec get_suites(file:filename()) -> [string()]. diff --git a/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes b/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes index 039e5e23f6..9294602211 100644 --- a/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes +++ b/lib/dialyzer/test/indent_SUITE_data/results/contracts_with_subtypes @@ -74,8 +74,12 @@ contracts_with_subtypes.erl:238:2: The pattern contracts_with_subtypes.erl:239:2: The pattern 'alpha' can never match the type {'ok', _, string()} -contracts_with_subtypes.erl:23:2: Invalid type specification for function contracts_with_subtypes:extract2/0. The success typing is +contracts_with_subtypes.erl:23:2: Invalid type specification for function contracts_with_subtypes:extract2/0. + The success typing is contracts_with_subtypes:extract2 () -> 'something' + But the spec is contracts_with_subtypes:extract2 + () -> 'ok' + The return types do not overlap contracts_with_subtypes.erl:240:2: The pattern {'ok', 42} can never match the type {'ok', _, string()} @@ -129,8 +133,12 @@ contracts_with_subtypes.erl:78:16: The call contracts_with_subtypes:foo2 contracts_with_subtypes.erl:79:16: The call contracts_with_subtypes:foo3 (5) breaks the contract (Arg1) -> Res when Arg2 :: atom(), Arg1 :: Arg2, Res :: atom() -contracts_with_subtypes.erl:7:2: Invalid type specification for function contracts_with_subtypes:extract/0. The success typing is +contracts_with_subtypes.erl:7:2: Invalid type specification for function contracts_with_subtypes:extract/0. + The success typing is contracts_with_subtypes:extract () -> 'something' + But the spec is contracts_with_subtypes:extract + () -> 'ok' + The return types do not overlap contracts_with_subtypes.erl:80:16: The call contracts_with_subtypes:foo4 (5) breaks the contract (Type) -> Type when Type :: atom() diff --git a/lib/dialyzer/test/indent_SUITE_data/results/record_update b/lib/dialyzer/test/indent_SUITE_data/results/record_update index 997b3ecb96..9ab8d478b6 100644 --- a/lib/dialyzer/test/indent_SUITE_data/results/record_update +++ b/lib/dialyzer/test/indent_SUITE_data/results/record_update @@ -1,3 +1,7 @@ -record_update.erl:7:2: Invalid type specification for function record_update:quux/2. The success typing is +record_update.erl:7:2: Invalid type specification for function record_update:quux/2. + The success typing is record_update:quux (#foo{bar :: atom()}, atom()) -> #foo{bar :: atom()} + But the spec is record_update:quux + (#foo{}, string()) -> #foo{} + They do not overlap in the 2nd argument diff --git a/lib/dialyzer/test/indent_SUITE_data/results/simple b/lib/dialyzer/test/indent_SUITE_data/results/simple index f33392d5bc..7fea96c502 100644 --- a/lib/dialyzer/test/indent_SUITE_data/results/simple +++ b/lib/dialyzer/test/indent_SUITE_data/results/simple @@ -83,8 +83,12 @@ rec_api.erl:29:5: Matching of pattern rec_api.erl:33:5: The attempt to match a term of type rec_adt:r1() against the pattern {'r1', 'a'} breaks the opacity of the term -rec_api.erl:35:2: Invalid type specification for function rec_api:adt_t1/1. The success typing is +rec_api.erl:35:2: Invalid type specification for function rec_api:adt_t1/1. + The success typing is rec_api:adt_t1 (#r1{f1 :: 'a'}) -> #r1{f1 :: 'a'} + But the spec is rec_api:adt_t1 + (rec_adt:r1()) -> rec_adt:r1() + They do not overlap in the 1st argument, and the return types do not overlap rec_api.erl:40:2: The specification for rec_api:adt_r1/0 has an opaque subtype rec_adt:r1() which is violated by the success typing () -> #r1{f1 :: 'a'} @@ -182,14 +186,26 @@ simple1_api.erl:342:8: Guard test simple1_api.erl:347:8: Guard test A :: simple1_adt:b1() =:= 'true' contains an opaque term as 1st argument -simple1_api.erl:355:2: Invalid type specification for function simple1_api:bool_adt_t6/1. The success typing is +simple1_api.erl:355:2: Invalid type specification for function simple1_api:bool_adt_t6/1. + The success typing is simple1_api:bool_adt_t6 ('true') -> 1 + But the spec is simple1_api:bool_adt_t6 + (simple1_adt:b1()) -> integer() + They do not overlap in the 1st argument simple1_api.erl:365:8: Clause guard cannot succeed. -simple1_api.erl:368:2: Invalid type specification for function simple1_api:bool_adt_t8/2. The success typing is +simple1_api.erl:368:2: Invalid type specification for function simple1_api:bool_adt_t8/2. + The success typing is simple1_api:bool_adt_t8 (boolean(), boolean()) -> 1 + But the spec is simple1_api:bool_adt_t8 + (simple1_adt:b1(), simple1_adt:b2()) -> integer() + They do not overlap in the 1st and 2nd arguments simple1_api.erl:378:8: Clause guard cannot succeed. -simple1_api.erl:381:2: Invalid type specification for function simple1_api:bool_adt_t9/2. The success typing is +simple1_api.erl:381:2: Invalid type specification for function simple1_api:bool_adt_t9/2. + The success typing is simple1_api:bool_adt_t9 ('false', 'false') -> 1 + But the spec is simple1_api:bool_adt_t9 + (simple1_adt:b1(), simple1_adt:b2()) -> integer() + They do not overlap in the 1st and 2nd arguments simple1_api.erl:407:12: The size simple1_adt:i1() breaks the opacity of A simple1_api.erl:418:9: The attempt to match a term of type diff --git a/lib/dialyzer/test/map_SUITE_data/results/contract_violation b/lib/dialyzer/test/map_SUITE_data/results/contract_violation index d0dd42a900..782e154100 100644 --- a/lib/dialyzer/test/map_SUITE_data/results/contract_violation +++ b/lib/dialyzer/test/map_SUITE_data/results/contract_violation @@ -1,3 +1,6 @@ contract_violation.erl:12:2: The pattern #{I:=Loc} can never match the type #{} -contract_violation.erl:16:2: Invalid type specification for function contract_violation:beam_disasm_lines/2. The success typing is ('none' | <<_:32,_:_*8>>,_) -> #{pos_integer()=>{'location',_,_}} +contract_violation.erl:16:2: Invalid type specification for function contract_violation:beam_disasm_lines/2. + The success typing is contract_violation:beam_disasm_lines('none' | <<_:32,_:_*8>>,_) -> #{pos_integer()=>{'location',_,_}} + But the spec is contract_violation:beam_disasm_lines(binary() | 'none',module()) -> lines() + The return types do not overlap diff --git a/lib/dialyzer/test/map_SUITE_data/results/opaque_key b/lib/dialyzer/test/map_SUITE_data/results/opaque_key index b70157f1af..c3df7a5560 100644 --- a/lib/dialyzer/test/map_SUITE_data/results/opaque_key +++ b/lib/dialyzer/test/map_SUITE_data/results/opaque_key @@ -1,9 +1,24 @@ -opaque_key_adt.erl:35:2: Invalid type specification for function opaque_key_adt:s2/0. The success typing is () -> #{3:='a'} -opaque_key_adt.erl:41:2: Invalid type specification for function opaque_key_adt:s4/0. The success typing is () -> #{1:='a'} -opaque_key_adt.erl:44:2: Invalid type specification for function opaque_key_adt:s5/0. The success typing is () -> #{2:=3} -opaque_key_adt.erl:56:2: Invalid type specification for function opaque_key_adt:smt1/0. The success typing is () -> #{3:='a'} -opaque_key_adt.erl:59:2: Invalid type specification for function opaque_key_adt:smt2/0. The success typing is () -> #{1:='a'} +opaque_key_adt.erl:35:2: Invalid type specification for function opaque_key_adt:s2/0. + The success typing is opaque_key_adt:s2() -> #{3:='a'} + But the spec is opaque_key_adt:s2() -> s(atom() | 3) + The return types do not overlap +opaque_key_adt.erl:41:2: Invalid type specification for function opaque_key_adt:s4/0. + The success typing is opaque_key_adt:s4() -> #{1:='a'} + But the spec is opaque_key_adt:s4() -> s(integer()) + The return types do not overlap +opaque_key_adt.erl:44:2: Invalid type specification for function opaque_key_adt:s5/0. + The success typing is opaque_key_adt:s5() -> #{2:=3} + But the spec is opaque_key_adt:s5() -> s(1) + The return types do not overlap +opaque_key_adt.erl:56:2: Invalid type specification for function opaque_key_adt:smt1/0. + The success typing is opaque_key_adt:smt1() -> #{3:='a'} + But the spec is opaque_key_adt:smt1() -> smt(1) + The return types do not overlap +opaque_key_adt.erl:59:2: Invalid type specification for function opaque_key_adt:smt2/0. + The success typing is opaque_key_adt:smt2() -> #{1:='a'} + But the spec is opaque_key_adt:smt2() -> smt(1) + The return types do not overlap opaque_key_use.erl:13:5: The test opaque_key_use:t() =:= opaque_key_use:t(_) can never evaluate to 'true' opaque_key_use.erl:24:5: Attempt to test for equality between a term of type opaque_key_adt:t(_) and a term of opaque type opaque_key_adt:t() opaque_key_use.erl:37:1: Function adt_mm1/0 has no local return diff --git a/lib/dialyzer/test/opaque_SUITE_data/results/int b/lib/dialyzer/test/opaque_SUITE_data/results/int index 42fd95e321..504013883f 100644 --- a/lib/dialyzer/test/opaque_SUITE_data/results/int +++ b/lib/dialyzer/test/opaque_SUITE_data/results/int @@ -1,3 +1,9 @@ -int_adt.erl:28:2: Invalid type specification for function int_adt:add_f/2. The success typing is (number() | int_adt:int(),float()) -> number() | int_adt:int() -int_adt.erl:32:2: Invalid type specification for function int_adt:div_f/2. The success typing is (number() | int_adt:int(),number() | int_adt:int()) -> float() +int_adt.erl:28:2: Invalid type specification for function int_adt:add_f/2. + The success typing is int_adt:add_f(number() | int_adt:int(),float()) -> number() | int_adt:int() + But the spec is int_adt:add_f(int(),int()) -> int() + They do not overlap in the 2nd argument +int_adt.erl:32:2: Invalid type specification for function int_adt:div_f/2. + The success typing is int_adt:div_f(number() | int_adt:int(),number() | int_adt:int()) -> float() + But the spec is int_adt:div_f(int(),int()) -> int() + The return types do not overlap diff --git a/lib/dialyzer/test/opaque_SUITE_data/results/multiple_wrong_opaques b/lib/dialyzer/test/opaque_SUITE_data/results/multiple_wrong_opaques index fd702bf1d6..0130be07b7 100644 --- a/lib/dialyzer/test/opaque_SUITE_data/results/multiple_wrong_opaques +++ b/lib/dialyzer/test/opaque_SUITE_data/results/multiple_wrong_opaques @@ -1,2 +1,5 @@ -multiple_wrong_opaques.erl:5:2: Invalid type specification for function multiple_wrong_opaques:weird/1. The success typing is ('gazonk') -> 42 +multiple_wrong_opaques.erl:5:2: Invalid type specification for function multiple_wrong_opaques:weird/1. + The success typing is multiple_wrong_opaques:weird('gazonk') -> 42 + But the spec is multiple_wrong_opaques:weird(dict:dict() | gb_trees:tree()) -> 42 + They do not overlap in the 1st argument diff --git a/lib/dialyzer/test/opaque_SUITE_data/results/para b/lib/dialyzer/test/opaque_SUITE_data/results/para index 0ba2a24996..77106c6afa 100644 --- a/lib/dialyzer/test/opaque_SUITE_data/results/para +++ b/lib/dialyzer/test/opaque_SUITE_data/results/para @@ -12,13 +12,22 @@ para2.erl:31:5: The test 'a' =:= 'b' can never evaluate to 'true' para2.erl:61:5: Attempt to test for equality between a term of type para2_adt:c2() and a term of opaque type para2_adt:c1() para2.erl:66:5: The test 'a' =:= 'b' can never evaluate to 'true' para2.erl:88:5: The test para2:circ(_) =:= para2:circ(_,_) can never evaluate to 'true' -para3.erl:28:2: Invalid type specification for function para3:ot2/0. The success typing is () -> 'foo' +para3.erl:28:2: Invalid type specification for function para3:ot2/0. + The success typing is para3:ot2() -> 'foo' + But the spec is para3:ot2() -> ot1() + The return types do not overlap para3.erl:36:5: The pattern {{{17}}} can never match the type {{{{{{_,_,_,_,_}}}}}} -para3.erl:55:2: Invalid type specification for function para3:t2/0. The success typing is () -> 'foo' +para3.erl:55:2: Invalid type specification for function para3:t2/0. + The success typing is para3:t2() -> 'foo' + But the spec is para3:t2() -> t1() + The return types do not overlap para3.erl:65:5: The attempt to match a term of type {{{{{para3_adt:ot1(_,_,_,_,_)}}}}} against the pattern {{{{{17}}}}} breaks the opacity of para3_adt:ot1(_,_,_,_,_) para3.erl:68:5: The pattern {{{{17}}}} can never match the type {{{{{para3_adt:ot1(_,_,_,_,_)}}}}} para3.erl:74:2: The specification for para3:exp_adt/0 has an opaque subtype para3_adt:exp1(_) which is violated by the success typing () -> 3 -para4.erl:31:2: Invalid type specification for function para4:t/1. The success typing is (para4:d_all() | para4:d_tuple()) -> [{atom() | integer(),atom() | integer()}] +para4.erl:31:2: Invalid type specification for function para4:t/1. + The success typing is para4:t(para4:d_all() | para4:d_tuple()) -> [{atom() | integer(),atom() | integer()}] + But the spec is para4:t(d_tuple()) -> [{tuple(),tuple()}] + The return types do not overlap para4.erl:79:5: The test para4_adt:int(_) =:= para4_adt:int(_) can never evaluate to 'true' para5.erl:13:5: Attempt to test for inequality between a term of type para5_adt:dd(_) and a term of opaque type para5_adt:d() para5.erl:8:5: The test para5_adt:d() =:= para5_adt:d() can never evaluate to 'true' diff --git a/lib/dialyzer/test/opaque_SUITE_data/results/simple b/lib/dialyzer/test/opaque_SUITE_data/results/simple index 4959d14f15..4c211a4425 100644 --- a/lib/dialyzer/test/opaque_SUITE_data/results/simple +++ b/lib/dialyzer/test/opaque_SUITE_data/results/simple @@ -21,7 +21,10 @@ rec_api.erl:123:5: The attempt to match a term of type #r3{f1::10} against the p rec_api.erl:24:18: Record construction #r1{f1::10} violates the declared type of field f1::rec_api:a() rec_api.erl:29:5: Matching of pattern {'r1', 10} tagged with a record name violates the declared type of #r1{f1::10} rec_api.erl:33:5: The attempt to match a term of type rec_adt:r1() against the pattern {'r1', 'a'} breaks the opacity of the term -rec_api.erl:35:2: Invalid type specification for function rec_api:adt_t1/1. The success typing is (#r1{f1::'a'}) -> #r1{f1::'a'} +rec_api.erl:35:2: Invalid type specification for function rec_api:adt_t1/1. + The success typing is rec_api:adt_t1(#r1{f1::'a'}) -> #r1{f1::'a'} + But the spec is rec_api:adt_t1(rec_adt:r1()) -> rec_adt:r1() + They do not overlap in the 1st argument, and the return types do not overlap rec_api.erl:40:2: The specification for rec_api:adt_r1/0 has an opaque subtype rec_adt:r1() which is violated by the success typing () -> #r1{f1::'a'} rec_api.erl:85:13: The attempt to match a term of type rec_adt:f() against the record field 'f' declared to be of type rec_api:f() breaks the opacity of the term rec_api.erl:99:18: Record construction #r2{f1::10} violates the declared type of field f1::rec_api:a() @@ -55,11 +58,20 @@ simple1_api.erl:319:16: Guard test not(and('true','true')) can never succeed simple1_api.erl:337:8: Clause guard cannot succeed. simple1_api.erl:342:8: Guard test B::simple1_adt:b2() =:= 'true' contains an opaque term as 1st argument simple1_api.erl:347:8: Guard test A::simple1_adt:b1() =:= 'true' contains an opaque term as 1st argument -simple1_api.erl:355:2: Invalid type specification for function simple1_api:bool_adt_t6/1. The success typing is ('true') -> 1 +simple1_api.erl:355:2: Invalid type specification for function simple1_api:bool_adt_t6/1. + The success typing is simple1_api:bool_adt_t6('true') -> 1 + But the spec is simple1_api:bool_adt_t6(simple1_adt:b1()) -> integer() + They do not overlap in the 1st argument simple1_api.erl:365:8: Clause guard cannot succeed. -simple1_api.erl:368:2: Invalid type specification for function simple1_api:bool_adt_t8/2. The success typing is (boolean(),boolean()) -> 1 +simple1_api.erl:368:2: Invalid type specification for function simple1_api:bool_adt_t8/2. + The success typing is simple1_api:bool_adt_t8(boolean(),boolean()) -> 1 + But the spec is simple1_api:bool_adt_t8(simple1_adt:b1(),simple1_adt:b2()) -> integer() + They do not overlap in the 1st and 2nd arguments simple1_api.erl:378:8: Clause guard cannot succeed. -simple1_api.erl:381:2: Invalid type specification for function simple1_api:bool_adt_t9/2. The success typing is ('false','false') -> 1 +simple1_api.erl:381:2: Invalid type specification for function simple1_api:bool_adt_t9/2. + The success typing is simple1_api:bool_adt_t9('false','false') -> 1 + But the spec is simple1_api:bool_adt_t9(simple1_adt:b1(),simple1_adt:b2()) -> integer() + They do not overlap in the 1st and 2nd arguments simple1_api.erl:407:12: The size simple1_adt:i1() breaks the opacity of A simple1_api.erl:418:9: The attempt to match a term of type non_neg_integer() against the variable A breaks the opacity of simple1_adt:i1() simple1_api.erl:425:9: The attempt to match a term of type non_neg_integer() against the variable B breaks the opacity of simple1_adt:i1() diff --git a/lib/dialyzer/test/small_SUITE_data/results/binary_nonempty b/lib/dialyzer/test/small_SUITE_data/results/binary_nonempty index 5275482a59..dbfaf63d6e 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/binary_nonempty +++ b/lib/dialyzer/test/small_SUITE_data/results/binary_nonempty @@ -1,16 +1,37 @@ binary_nonempty.erl:12:1: Function t2/0 has no local return binary_nonempty.erl:13:8: The call binary_nonempty:t2(<<>>) breaks the contract (nonempty_binary()) -> 'foo' -binary_nonempty.erl:15:2: Invalid type specification for function binary_nonempty:t2/1. The success typing is (<<>>) -> 'foo' +binary_nonempty.erl:15:2: Invalid type specification for function binary_nonempty:t2/1. + The success typing is binary_nonempty:t2(<<>>) -> 'foo' + But the spec is binary_nonempty:t2(nonempty_binary()) -> 'foo' + They do not overlap in the 1st argument binary_nonempty.erl:19:1: Function t3/0 has no local return binary_nonempty.erl:20:8: The call binary_nonempty:t3(<<>>) breaks the contract (<<_:1,_:_*1>>) -> 'foo' -binary_nonempty.erl:22:2: Invalid type specification for function binary_nonempty:t3/1. The success typing is (<<>>) -> 'foo' +binary_nonempty.erl:22:2: Invalid type specification for function binary_nonempty:t3/1. + The success typing is binary_nonempty:t3(<<>>) -> 'foo' + But the spec is binary_nonempty:t3(<<_:1,_:_*1>>) -> 'foo' + They do not overlap in the 1st argument binary_nonempty.erl:26:1: Function t4/0 has no local return binary_nonempty.erl:27:8: The call binary_nonempty:t4(<<>>) breaks the contract (<<_:8,_:_*8>>) -> 'foo' -binary_nonempty.erl:29:2: Invalid type specification for function binary_nonempty:t4/1. The success typing is (<<>>) -> 'foo' -binary_nonempty.erl:33:2: Invalid type specification for function binary_nonempty:t5/1. The success typing is (<<>>) -> 'foo' -binary_nonempty.erl:38:2: Invalid type specification for function binary_nonempty:t6/1. The success typing is (<<_:8>>) -> 'foo' -binary_nonempty.erl:43:2: Invalid type specification for function binary_nonempty:t7/1. The success typing is (<<_:1>>) -> 'foo' +binary_nonempty.erl:29:2: Invalid type specification for function binary_nonempty:t4/1. + The success typing is binary_nonempty:t4(<<>>) -> 'foo' + But the spec is binary_nonempty:t4(<<_:8,_:_*8>>) -> 'foo' + They do not overlap in the 1st argument +binary_nonempty.erl:33:2: Invalid type specification for function binary_nonempty:t5/1. + The success typing is binary_nonempty:t5(<<>>) -> 'foo' + But the spec is binary_nonempty:t5(nonempty_binary()) -> 'foo' + They do not overlap in the 1st argument +binary_nonempty.erl:38:2: Invalid type specification for function binary_nonempty:t6/1. + The success typing is binary_nonempty:t6(<<_:8>>) -> 'foo' + But the spec is binary_nonempty:t6(<<>>) -> 'foo' + They do not overlap in the 1st argument +binary_nonempty.erl:43:2: Invalid type specification for function binary_nonempty:t7/1. + The success typing is binary_nonempty:t7(<<_:1>>) -> 'foo' + But the spec is binary_nonempty:t7(<<>>) -> 'foo' + They do not overlap in the 1st argument binary_nonempty.erl:5:1: Function t1/0 has no local return binary_nonempty.erl:6:8: The call binary_nonempty:t1(<<>>) breaks the contract (nonempty_bitstring()) -> 'foo' -binary_nonempty.erl:8:2: Invalid type specification for function binary_nonempty:t1/1. The success typing is (<<>>) -> 'foo' +binary_nonempty.erl:8:2: Invalid type specification for function binary_nonempty:t1/1. + The success typing is binary_nonempty:t1(<<>>) -> 'foo' + But the spec is binary_nonempty:t1(nonempty_bitstring()) -> 'foo' + They do not overlap in the 1st argument diff --git a/lib/dialyzer/test/small_SUITE_data/results/binary_redef2 b/lib/dialyzer/test/small_SUITE_data/results/binary_redef2 index 71968b801b..19559b6dfb 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/binary_redef2 +++ b/lib/dialyzer/test/small_SUITE_data/results/binary_redef2 @@ -1,3 +1,9 @@ -binary_redef2.erl:15:2: Invalid type specification for function binary_redef2:t1/1. The success typing is (3) -> 6 -binary_redef2.erl:20:2: Invalid type specification for function binary_redef2:new/0. The success typing is () -> 3 +binary_redef2.erl:15:2: Invalid type specification for function binary_redef2:t1/1. + The success typing is binary_redef2:t1(3) -> 6 + But the spec is binary_redef2:t1(nonempty_bitstring()) -> nonempty_bitstring() + They do not overlap in the 1st argument, and the return types do not overlap +binary_redef2.erl:20:2: Invalid type specification for function binary_redef2:new/0. + The success typing is binary_redef2:new() -> 3 + But the spec is binary_redef2:new() -> nonempty_binary() + The return types do not overlap diff --git a/lib/dialyzer/test/small_SUITE_data/results/chars b/lib/dialyzer/test/small_SUITE_data/results/chars index ec7b468e43..a91e21d181 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/chars +++ b/lib/dialyzer/test/small_SUITE_data/results/chars @@ -1,4 +1,7 @@ -chars.erl:37:2: Invalid type specification for function chars:f/1. The success typing is (#{'b':=50}) -> 'ok' +chars.erl:37:2: Invalid type specification for function chars:f/1. + The success typing is chars:f(#{'b':=50}) -> 'ok' + But the spec is chars:f(#{'a':=49,'b'=>50,'c'=>51}) -> 'ok' + They do not overlap in the 1st argument chars.erl:40:11: The call chars:f(#{'b'=>50}) breaks the contract (#{'a':=49,'b'=>50,'c'=>51}) -> 'ok' chars.erl:40:1: Function t1/0 has no local return diff --git a/lib/dialyzer/test/small_SUITE_data/results/contract5 b/lib/dialyzer/test/small_SUITE_data/results/contract5 index 10ea8ca362..9ffccbc19b 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/contract5 +++ b/lib/dialyzer/test/small_SUITE_data/results/contract5 @@ -1,2 +1,5 @@ -contract5.erl:13:2: Invalid type specification for function contract5:t/0. The success typing is () -> #bar{baz::'not_a_boolean'} +contract5.erl:13:2: Invalid type specification for function contract5:t/0. + The success typing is contract5:t() -> #bar{baz::'not_a_boolean'} + But the spec is contract5:t() -> #bar{baz::boolean()} + The return types do not overlap diff --git a/lib/dialyzer/test/small_SUITE_data/results/contracts_with_subtypes b/lib/dialyzer/test/small_SUITE_data/results/contracts_with_subtypes index 44fd6056bd..8645aa9078 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/contracts_with_subtypes +++ b/lib/dialyzer/test/small_SUITE_data/results/contracts_with_subtypes @@ -20,7 +20,10 @@ contracts_with_subtypes.erl:218:2: The pattern 42 can never match the type {'ok' contracts_with_subtypes.erl:235:3: The pattern 1 can never match the type string() contracts_with_subtypes.erl:238:2: The pattern {'ok', _} can never match the type {'ok',_,string()} contracts_with_subtypes.erl:239:2: The pattern 'alpha' can never match the type {'ok',_,string()} -contracts_with_subtypes.erl:23:2: Invalid type specification for function contracts_with_subtypes:extract2/0. The success typing is () -> 'something' +contracts_with_subtypes.erl:23:2: Invalid type specification for function contracts_with_subtypes:extract2/0. + The success typing is contracts_with_subtypes:extract2() -> 'something' + But the spec is contracts_with_subtypes:extract2() -> 'ok' + The return types do not overlap contracts_with_subtypes.erl:240:2: The pattern {'ok', 42} can never match the type {'ok',_,string()} contracts_with_subtypes.erl:241:2: The pattern 42 can never match the type {'ok',_,string()} contracts_with_subtypes.erl:267:1: Function flat_ets_new_t/0 has no local return @@ -30,7 +33,10 @@ contracts_with_subtypes.erl:295:22: The call contracts_with_subtypes:factored_et contracts_with_subtypes.erl:77:16: The call contracts_with_subtypes:foo1(5) breaks the contract (Arg1) -> Res when Arg1 :: atom(), Res :: atom() contracts_with_subtypes.erl:78:16: The call contracts_with_subtypes:foo2(5) breaks the contract (Arg1) -> Res when Arg1 :: Arg2, Arg2 :: atom(), Res :: atom() contracts_with_subtypes.erl:79:16: The call contracts_with_subtypes:foo3(5) breaks the contract (Arg1) -> Res when Arg2 :: atom(), Arg1 :: Arg2, Res :: atom() -contracts_with_subtypes.erl:7:2: Invalid type specification for function contracts_with_subtypes:extract/0. The success typing is () -> 'something' +contracts_with_subtypes.erl:7:2: Invalid type specification for function contracts_with_subtypes:extract/0. + The success typing is contracts_with_subtypes:extract() -> 'something' + But the spec is contracts_with_subtypes:extract() -> 'ok' + The return types do not overlap contracts_with_subtypes.erl:80:16: The call contracts_with_subtypes:foo4(5) breaks the contract (Type) -> Type when Type :: atom() contracts_with_subtypes.erl:81:16: The call contracts_with_subtypes:foo5(5) breaks the contract (Type::atom()) -> Type::atom() contracts_with_subtypes.erl:82:16: The call contracts_with_subtypes:foo6(5) breaks the contract (Type) -> Type when Type :: atom() diff --git a/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum b/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum index cf44c15458..b53b251a39 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum +++ b/lib/dialyzer/test/small_SUITE_data/results/empty_list_infimum @@ -1,2 +1,5 @@ -empty_list_infimum.erl:38:2: Invalid type specification for function empty_list_infimum:list_vhost_permissions/1. The success typing is (_) -> [[{_,_}]] +empty_list_infimum.erl:38:2: Invalid type specification for function empty_list_infimum:list_vhost_permissions/1. + The success typing is empty_list_infimum:list_vhost_permissions(_) -> [[{_,_}]] + But the spec is empty_list_infimum:list_vhost_permissions(vhost()) -> infos() + The return types do not overlap diff --git a/lib/dialyzer/test/small_SUITE_data/results/invalid_spec_2 b/lib/dialyzer/test/small_SUITE_data/results/invalid_spec_2 index bfada119a2..a8026b787f 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/invalid_spec_2 +++ b/lib/dialyzer/test/small_SUITE_data/results/invalid_spec_2 @@ -1,2 +1,5 @@ -scala_user.erl:5:2: Invalid type specification for function scala_user:is_list/2. The success typing is (maybe_improper_list() | tuple(),_) -> boolean() +scala_user.erl:5:2: Invalid type specification for function scala_user:is_list/2. + The success typing is scala_user:is_list(maybe_improper_list() | tuple(),_) -> boolean() + But the spec is scala_user:is_list(atom(),scala_data:data()) -> boolean() + They do not overlap in the 1st argument diff --git a/lib/dialyzer/test/small_SUITE_data/results/invalid_specs b/lib/dialyzer/test/small_SUITE_data/results/invalid_specs index 0de8f0fcb4..306be3f76a 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/invalid_specs +++ b/lib/dialyzer/test/small_SUITE_data/results/invalid_specs @@ -1,3 +1,6 @@ -invalid_spec1.erl:5:2: Invalid type specification for function invalid_spec1:get_plan_dirty/1. The success typing is ([string()]) -> {maybe_improper_list(),[atom()]} +invalid_spec1.erl:5:2: Invalid type specification for function invalid_spec1:get_plan_dirty/1. + The success typing is invalid_spec1:get_plan_dirty([string()]) -> {maybe_improper_list(),[atom()]} + But the spec is invalid_spec1:get_plan_dirty([string()]) -> {{atom(),any()},[atom()]} + The return types do not overlap invalid_spec2.erl:5:1: Function foo/0 has no local return diff --git a/lib/dialyzer/test/small_SUITE_data/results/maps_sum b/lib/dialyzer/test/small_SUITE_data/results/maps_sum index 83e7c73ef2..df2a90387b 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/maps_sum +++ b/lib/dialyzer/test/small_SUITE_data/results/maps_sum @@ -1,4 +1,7 @@ -maps_sum.erl:15:2: Invalid type specification for function maps_sum:wrong1/1. The success typing is (maps:iterator(_,_) | map()) -> any() +maps_sum.erl:15:2: Invalid type specification for function maps_sum:wrong1/1. + The success typing is maps_sum:wrong1(maps:iterator(_,_) | map()) -> any() + But the spec is maps_sum:wrong1([{atom(),term()}]) -> integer() + They do not overlap in the 1st argument maps_sum.erl:26:1: Function wrong2/1 has no local return maps_sum.erl:27:17: The call lists:foldl(fun((_,_,_) -> any()),0,Data::any()) will never return since it differs in the 1st argument from the success typing arguments: (fun((_,_) -> any()),any(),[any()]) diff --git a/lib/dialyzer/test/small_SUITE_data/results/predef b/lib/dialyzer/test/small_SUITE_data/results/predef index f57f78d59e..e89dd8db87 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/predef +++ b/lib/dialyzer/test/small_SUITE_data/results/predef @@ -1,8 +1,29 @@ -predef.erl:19:2: Invalid type specification for function predef:array/1. The success typing is (array:array(_)) -> array:array(_) -predef.erl:24:2: Invalid type specification for function predef:dict/1. The success typing is (dict:dict(_,_)) -> dict:dict(_,_) -predef.erl:29:2: Invalid type specification for function predef:digraph/1. The success typing is (digraph:graph()) -> [any()] -predef.erl:39:2: Invalid type specification for function predef:gb_set/1. The success typing is (gb_sets:set(_)) -> gb_sets:set(_) -predef.erl:44:2: Invalid type specification for function predef:gb_tree/1. The success typing is (gb_trees:tree(_,_)) -> gb_trees:tree(_,_) -predef.erl:49:2: Invalid type specification for function predef:queue/1. The success typing is (queue:queue(_)) -> queue:queue(_) -predef.erl:54:2: Invalid type specification for function predef:set/1. The success typing is (sets:set(_)) -> sets:set(_) +predef.erl:19:2: Invalid type specification for function predef:array/1. + The success typing is predef:array(array:array(_)) -> array:array(_) + But the spec is predef:array(array()) -> array:array() + They do not overlap in the 1st argument +predef.erl:24:2: Invalid type specification for function predef:dict/1. + The success typing is predef:dict(dict:dict(_,_)) -> dict:dict(_,_) + But the spec is predef:dict(dict()) -> dict:dict() + They do not overlap in the 1st argument +predef.erl:29:2: Invalid type specification for function predef:digraph/1. + The success typing is predef:digraph(digraph:graph()) -> [any()] + But the spec is predef:digraph(digraph()) -> [digraph:edge()] + They do not overlap in the 1st argument +predef.erl:39:2: Invalid type specification for function predef:gb_set/1. + The success typing is predef:gb_set(gb_sets:set(_)) -> gb_sets:set(_) + But the spec is predef:gb_set(gb_set()) -> gb_sets:set() + They do not overlap in the 1st argument +predef.erl:44:2: Invalid type specification for function predef:gb_tree/1. + The success typing is predef:gb_tree(gb_trees:tree(_,_)) -> gb_trees:tree(_,_) + But the spec is predef:gb_tree(gb_tree()) -> gb_trees:tree() + They do not overlap in the 1st argument +predef.erl:49:2: Invalid type specification for function predef:queue/1. + The success typing is predef:queue(queue:queue(_)) -> queue:queue(_) + But the spec is predef:queue(queue()) -> queue:queue() + They do not overlap in the 1st argument +predef.erl:54:2: Invalid type specification for function predef:set/1. + The success typing is predef:set(sets:set(_)) -> sets:set(_) + But the spec is predef:set(set()) -> sets:set() + They do not overlap in the 1st argument diff --git a/lib/dialyzer/test/small_SUITE_data/results/record_update b/lib/dialyzer/test/small_SUITE_data/results/record_update index b61d2e66b3..d2747d0440 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/record_update +++ b/lib/dialyzer/test/small_SUITE_data/results/record_update @@ -1,2 +1,5 @@ -record_update.erl:7:2: Invalid type specification for function record_update:quux/2. The success typing is (#foo{bar::atom()},atom()) -> #foo{bar::atom()} +record_update.erl:7:2: Invalid type specification for function record_update:quux/2. + The success typing is record_update:quux(#foo{bar::atom()},atom()) -> #foo{bar::atom()} + But the spec is record_update:quux(#foo{},string()) -> #foo{} + They do not overlap in the 2nd argument diff --git a/lib/dialyzer/test/small_SUITE_data/results/tuple_set_crash b/lib/dialyzer/test/small_SUITE_data/results/tuple_set_crash index 4d72467a06..9e415b469b 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/tuple_set_crash +++ b/lib/dialyzer/test/small_SUITE_data/results/tuple_set_crash @@ -1,12 +1,30 @@ -tuple_set_crash.erl:103:2: Invalid type specification for function tuple_set_crash:parse_device_properties/1. The success typing is (<<_:48>>) -> [{'controller_description',binary()} | {'controller_name',binary()} | {'controller_status',byte()} | {'fw_version',<<_:24>>}] -tuple_set_crash.erl:123:2: Invalid type specification for function tuple_set_crash:parse_video_target_info/1. The success typing is (<<_:48>>) -> [{'status',byte()} | {'target_id',non_neg_integer()},...] -tuple_set_crash.erl:127:2: Invalid type specification for function tuple_set_crash:parse_audio_target_info/1. The success typing is (<<_:48>>) -> [{'master_volume',char()} | {'status',byte()} | {'target_id',non_neg_integer()},...] -tuple_set_crash.erl:138:2: Invalid type specification for function tuple_set_crash:parse_av_device_info/1. The success typing is (<<_:48>>) -> [{'address',byte()} | {'device_id',non_neg_integer()} | {'model',binary()} | {'status',byte()},...] +tuple_set_crash.erl:103:2: Invalid type specification for function tuple_set_crash:parse_device_properties/1. + The success typing is tuple_set_crash:parse_device_properties(<<_:48>>) -> [{'controller_description',binary()} | {'controller_name',binary()} | {'controller_status',byte()} | {'fw_version',<<_:24>>}] + But the spec is tuple_set_crash:parse_device_properties(binary()) -> config_change() + The return types do not overlap +tuple_set_crash.erl:123:2: Invalid type specification for function tuple_set_crash:parse_video_target_info/1. + The success typing is tuple_set_crash:parse_video_target_info(<<_:48>>) -> [{'status',byte()} | {'target_id',non_neg_integer()},...] + But the spec is tuple_set_crash:parse_video_target_info(binary()) -> config_change() + The return types do not overlap +tuple_set_crash.erl:127:2: Invalid type specification for function tuple_set_crash:parse_audio_target_info/1. + The success typing is tuple_set_crash:parse_audio_target_info(<<_:48>>) -> [{'master_volume',char()} | {'status',byte()} | {'target_id',non_neg_integer()},...] + But the spec is tuple_set_crash:parse_audio_target_info(binary()) -> [config_change()] + The return types do not overlap +tuple_set_crash.erl:138:2: Invalid type specification for function tuple_set_crash:parse_av_device_info/1. + The success typing is tuple_set_crash:parse_av_device_info(<<_:48>>) -> [{'address',byte()} | {'device_id',non_neg_integer()} | {'model',binary()} | {'status',byte()},...] + But the spec is tuple_set_crash:parse_av_device_info(binary()) -> [config_change()] + The return types do not overlap tuple_set_crash.erl:141:25: The pattern <<TargetId:32/integer-little-unit:1,Rest1/binary>> can never match the type <<_:8>> -tuple_set_crash.erl:155:2: Invalid type specification for function tuple_set_crash:parse_video_output_info/1. The success typing is (<<_:48>>) -> [{'audio_volume',char()} | {'display_type',binary()} | {'output_id',non_neg_integer()},...] +tuple_set_crash.erl:155:2: Invalid type specification for function tuple_set_crash:parse_video_output_info/1. + The success typing is tuple_set_crash:parse_video_output_info(<<_:48>>) -> [{'audio_volume',char()} | {'display_type',binary()} | {'output_id',non_neg_integer()},...] + But the spec is tuple_set_crash:parse_video_output_info(binary()) -> [config_change()] + The return types do not overlap tuple_set_crash.erl:158:25: The pattern <<DeviceId:32/integer-little-unit:1,Rest1/binary>> can never match the type <<_:8>> -tuple_set_crash.erl:171:2: Invalid type specification for function tuple_set_crash:parse_audio_output_info/1. The success typing is (<<_:48>>) -> [{'output_id',non_neg_integer()},...] +tuple_set_crash.erl:171:2: Invalid type specification for function tuple_set_crash:parse_audio_output_info/1. + The success typing is tuple_set_crash:parse_audio_output_info(<<_:48>>) -> [{'output_id',non_neg_integer()},...] + But the spec is tuple_set_crash:parse_audio_output_info(binary()) -> [config_change()] + The return types do not overlap tuple_set_crash.erl:174:25: The pattern <<DeviceId:32/integer-little-unit:1,Rest1/binary>> can never match the type <<_:8>> tuple_set_crash.erl:177:25: The pattern <<AudioVolume:16/integer-little-unit:1,Rest2/binary>> can never match the type <<_:8>> tuple_set_crash.erl:180:25: The pattern <<Delay:16/integer-little-unit:1,_Padding/binary>> can never match the type <<_:8>> diff --git a/lib/dialyzer/test/small_SUITE_data/results/types_arity b/lib/dialyzer/test/small_SUITE_data/results/types_arity index fae7455996..9842bad61b 100644 --- a/lib/dialyzer/test/small_SUITE_data/results/types_arity +++ b/lib/dialyzer/test/small_SUITE_data/results/types_arity @@ -1,2 +1,5 @@ -types_arity.erl:16:2: Invalid type specification for function types_arity:test2/0. The success typing is () -> {'node','a','nil','nil'} +types_arity.erl:16:2: Invalid type specification for function types_arity:test2/0. + The success typing is types_arity:test2() -> {'node','a','nil','nil'} + But the spec is types_arity:test2() -> tree() + The return types do not overlap -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor