Skip to content

Commit 550690e

Browse files
committed
dialyzer_dataflow: Fix brainfart in bind_checked_inf/4
`unit` can't be bound any more than `none` can. This resulted in slightly improved analysis in some cases, taking notice of more functions in OTP that lacked a local return, so I've added specs to those functions in order to silence the warnings. The pattern for that is: ```erlang try function_that_returns_unit() catch _:_ -> error(xyz) end ``` Previously, this expression was treated as returning unit() even though it could only ever return none(), as the wrapped function would never return.
1 parent 0e372eb commit 550690e

File tree

6 files changed

+32
-5
lines changed

6 files changed

+32
-5
lines changed

lib/debugger/src/dbg_wx_view.erl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ stop() ->
5555
%% Main loop and message handling
5656
%%====================================================================
5757

58+
-spec init(term(), term(), term(), term()) -> no_return().
5859
init(GS, Env, Mod, Title) ->
5960
wx:set_env(Env),
6061
%% Subscribe to messages from the interpreter

lib/dialyzer/src/dialyzer_dataflow.erl

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1677,17 +1677,17 @@ bitstr_bitsize_type(Size) ->
16771677
any
16781678
end.
16791679

1680-
%% Return the infimum (meet) of ExpectedType and Type if is not
1681-
%% t_none(), and raise a bind_error() it is t_none().
1680+
%% Return the infimum (meet) of ExpectedType and Type if it describes a
1681+
%% possible value (not 'none' or 'unit'), otherwise raise a bind_error().
16821682
bind_checked_inf(Pat, ExpectedType, Type, Opaques) ->
16831683
Inf = t_inf(ExpectedType, Type, Opaques),
1684-
case t_is_none(Inf) of
1684+
case t_is_none_or_unit(Inf) of
16851685
true ->
16861686
case t_find_opaque_mismatch(ExpectedType, Type, Opaques) of
1687-
{ok, T1, T2} ->
1687+
{ok, T1, T2} ->
16881688
bind_error([Pat], T1, T2, opaque);
16891689
error ->
1690-
bind_error([Pat], Type, t_none(), bind)
1690+
bind_error([Pat], Type, Inf, bind)
16911691
end;
16921692
false ->
16931693
Inf
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
2+
gh6580.erl:11:21: The pattern <[_ | _], _> can never match the type <[],<<>>>
3+
gh6580.erl:5:1: Function f/0 has no local return
4+
gh6580.erl:6:5: The created fun has no local return
5+
gh6580.erl:6:5: The pattern <[], _> can never match the type <<<>>,<<>>>
6+
gh6580.erl:6:5: The pattern <[_ | _], _> can never match the type <<<>>,<<>>>
7+
gh6580.erl:9:13: Fun application with arguments (<<>>,<<>>) will never return since it differs in the 1st argument from the success typing arguments: ([],any())
Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
-module(gh6580).
2+
-export([f/0]).
3+
4+
%% GH-6580: dialyzer would crash when binding an impossible cons.
5+
f() ->
6+
<<
7+
0
8+
|| _ <-
9+
case ok of
10+
X ->
11+
<<0 || _ <- []>>
12+
end,
13+
X <- 0,
14+
#{X := Y} <- 0
15+
>>.

lib/reltool/src/reltool_app_win.erl

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,7 @@ open_mod(Pid, ModName) ->
9898
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
9999
%% Server
100100

101+
-spec init(term(), term(), term(), term(), term()) -> no_return().
101102
init(Parent, WxEnv, Xref, C, AppName) ->
102103
try
103104
do_init(Parent, WxEnv, Xref, C, AppName)

lib/stdlib/src/peer.erl

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -926,6 +926,7 @@ start_orphan_supervision() ->
926926

927927
-record(peer_sup_state, {parent, channel, in_sup_tree}).
928928

929+
-spec init_supervision(term(), term()) -> no_return().
929930
init_supervision(Parent, InSupTree) ->
930931
try
931932
process_flag(priority, high),
@@ -1055,6 +1056,7 @@ origin_link(MRef, Origin) ->
10551056
origin_link(MRef, Origin)
10561057
end.
10571058

1059+
-spec io_server() -> no_return().
10581060
io_server() ->
10591061
try
10601062
process_flag(trap_exit, true),
@@ -1068,6 +1070,7 @@ io_server() ->
10681070
erlang:halt(1)
10691071
end.
10701072

1073+
-spec tcp_init([term()], term()) -> no_return().
10711074
tcp_init(IpList, Port) ->
10721075
try
10731076
Sock = loop_connect(IpList, Port),

0 commit comments

Comments
 (0)