Skip to content

Commit

Permalink
dialyzer_dataflow: Fix bug in bind_checked_inf/4
Browse files Browse the repository at this point in the history
`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.
  • Loading branch information
jhogberg committed Dec 21, 2022
1 parent 0e372eb commit 3dc51db
Show file tree
Hide file tree
Showing 6 changed files with 32 additions and 5 deletions.
1 change: 1 addition & 0 deletions lib/debugger/src/dbg_wx_view.erl
Original file line number Diff line number Diff line change
Expand Up @@ -55,6 +55,7 @@ stop() ->
%% Main loop and message handling
%%====================================================================

-spec init(term(), term(), term(), term()) -> no_return().
init(GS, Env, Mod, Title) ->
wx:set_env(Env),
%% Subscribe to messages from the interpreter
Expand Down
10 changes: 5 additions & 5 deletions lib/dialyzer/src/dialyzer_dataflow.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1677,17 +1677,17 @@ bitstr_bitsize_type(Size) ->
any
end.

%% Return the infimum (meet) of ExpectedType and Type if is not
%% t_none(), and raise a bind_error() it is t_none().
%% Return the infimum (meet) of ExpectedType and Type if it describes a
%% possible value (not 'none' or 'unit'), otherwise raise a bind_error().
bind_checked_inf(Pat, ExpectedType, Type, Opaques) ->
Inf = t_inf(ExpectedType, Type, Opaques),
case t_is_none(Inf) of
case t_is_none_or_unit(Inf) of
true ->
case t_find_opaque_mismatch(ExpectedType, Type, Opaques) of
{ok, T1, T2} ->
{ok, T1, T2} ->
bind_error([Pat], T1, T2, opaque);
error ->
bind_error([Pat], Type, t_none(), bind)
bind_error([Pat], Type, Inf, bind)
end;
false ->
Inf
Expand Down
7 changes: 7 additions & 0 deletions lib/dialyzer/test/user_SUITE_data/results/gh6580
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@

gh6580.erl:11:21: The pattern <[_ | _], _> can never match the type <[],<<>>>
gh6580.erl:5:1: Function f/0 has no local return
gh6580.erl:6:5: The created fun has no local return
gh6580.erl:6:5: The pattern <[], _> can never match the type <<<>>,<<>>>
gh6580.erl:6:5: The pattern <[_ | _], _> can never match the type <<<>>,<<>>>
gh6580.erl:9:13: Fun application with arguments (<<>>,<<>>) will never return since it differs in the 1st argument from the success typing arguments: ([],any())
15 changes: 15 additions & 0 deletions lib/dialyzer/test/user_SUITE_data/src/gh6580.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
-module(gh6580).
-export([f/0]).

%% GH-6580: dialyzer would crash when binding an impossible cons.
f() ->
<<
0
|| _ <-
case ok of
X ->
<<0 || _ <- []>>
end,
X <- 0,
#{X := Y} <- 0
>>.
1 change: 1 addition & 0 deletions lib/reltool/src/reltool_app_win.erl
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,7 @@ open_mod(Pid, ModName) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
%% Server

-spec init(term(), term(), term(), term(), term()) -> no_return().
init(Parent, WxEnv, Xref, C, AppName) ->
try
do_init(Parent, WxEnv, Xref, C, AppName)
Expand Down
3 changes: 3 additions & 0 deletions lib/stdlib/src/peer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -926,6 +926,7 @@ start_orphan_supervision() ->

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

-spec init_supervision(term(), term()) -> no_return().
init_supervision(Parent, InSupTree) ->
try
process_flag(priority, high),
Expand Down Expand Up @@ -1055,6 +1056,7 @@ origin_link(MRef, Origin) ->
origin_link(MRef, Origin)
end.

-spec io_server() -> no_return().
io_server() ->
try
process_flag(trap_exit, true),
Expand All @@ -1068,6 +1070,7 @@ io_server() ->
erlang:halt(1)
end.

-spec tcp_init([term()], term()) -> no_return().
tcp_init(IpList, Port) ->
try
Sock = loop_connect(IpList, Port),
Expand Down

0 comments on commit 3dc51db

Please sign in to comment.