Skip to content

Commit 14af146

Browse files
committed
Eliminate Dialyzer crash for ill-typed code
Closes #6419
1 parent 19bce3c commit 14af146

File tree

4 files changed

+49
-15
lines changed

4 files changed

+49
-15
lines changed

lib/dialyzer/src/dialyzer_dataflow.erl

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1599,7 +1599,8 @@ bind_bin_segs([Seg|Segs], BinType, Acc, Map, State) ->
15991599
Val = cerl:bitstr_val(Seg),
16001600
SegType = cerl:concrete(cerl:bitstr_type(Seg)),
16011601
UnitVal = cerl:concrete(cerl:bitstr_unit(Seg)),
1602-
case cerl:bitstr_bitsize(Seg) of
1602+
Size = cerl:bitstr_size(Seg),
1603+
case bitstr_bitsize_type(Size) of
16031604
all ->
16041605
binary = SegType, [] = Segs, %% just an assert
16051606
T = t_inf(t_bitstr(UnitVal, 0), BinType),
@@ -1613,8 +1614,7 @@ bind_bin_segs([Seg|Segs], BinType, Acc, Map, State) ->
16131614
Map, State, false, []),
16141615
Type = t_binary(),
16151616
bind_bin_segs(Segs, BinType, [Type|Acc], Map1, State);
1616-
BitSz when is_integer(BitSz); BitSz =:= any ->
1617-
Size = cerl:bitstr_size(Seg),
1617+
any ->
16181618
{Map1, [SizeType]} = do_bind_pat_vars([Size], [t_non_neg_integer()],
16191619
Map, State, false, []),
16201620
Opaques = State#state.opaques,
@@ -1665,6 +1665,18 @@ bind_bin_segs([Seg|Segs], BinType, Acc, Map, State) ->
16651665
bind_bin_segs([], _BinType, Acc, Map, _State) ->
16661666
{Map, lists:reverse(Acc)}.
16671667

1668+
bitstr_bitsize_type(Size) ->
1669+
case cerl:is_literal(Size) of
1670+
true ->
1671+
case cerl:concrete(Size) of
1672+
all -> all;
1673+
undefined -> utf;
1674+
_ -> any
1675+
end;
1676+
false ->
1677+
any
1678+
end.
1679+
16681680
%% Return the infimum (meet) of ExpectedType and Type if is not
16691681
%% t_none(), and raise a bind_error() it is t_none().
16701682
bind_checked_inf(Pat, ExpectedType, Type, Opaques) ->

lib/dialyzer/src/dialyzer_typesig.erl

Lines changed: 18 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -255,17 +255,24 @@ traverse(Tree, DefinedVars, State) ->
255255
{State1, [SizeType, ValType]} =
256256
traverse_list([Size, Val], DefinedVars, State),
257257
{State2, TypeConstr, BinValTypeConstr} =
258-
case cerl:bitstr_bitsize(Tree) of
259-
all ->
260-
T = t_bitstr(UnitVal, 0),
261-
{State1, T, T};
262-
utf ->
263-
%% contains an integer number of bytes
264-
T = t_binary(),
265-
{State1, T, T};
266-
N when is_integer(N) ->
267-
{State1, t_bitstr(0, N), t_bitstr(1, N)};
268-
any -> % Size is not a literal
258+
case cerl:is_literal(Size) of
259+
true ->
260+
case cerl:concrete(Size) of
261+
all ->
262+
T = t_bitstr(UnitVal, 0),
263+
{State1, T, T};
264+
undefined -> %utf-8/16/32
265+
%% contains an integer number of bytes
266+
T = t_binary(),
267+
{State1, T, T};
268+
N0 when is_integer(N0) ->
269+
N = N0 * UnitVal,
270+
{State1, t_bitstr(0, N), t_bitstr(1, N)};
271+
_ ->
272+
{State1, t_none(), t_none()}
273+
end;
274+
false ->
275+
%% Size is not a literal
269276
T1 = ?mk_fun_var(bitstr_constr(SizeType, UnitVal), [SizeType]),
270277
T2 =
271278
?mk_fun_var(bitstr_constr(SizeType, UnitVal, match), [SizeType]),

lib/dialyzer/test/small_SUITE_data/results/bs_fail_constr

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,10 @@ bs_fail_constr.erl:11:1: Function w3/1 has no local return
33
bs_fail_constr.erl:12:8: Binary construction will fail since the size field S in segment 42:S has type neg_integer()
44
bs_fail_constr.erl:14:1: Function w4/1 has no local return
55
bs_fail_constr.erl:15:5: Binary construction will fail since the value field V in segment V/utf32 has type float()
6+
bs_fail_constr.erl:18:1: Function bad_size_1/1 has no local return
7+
bs_fail_constr.erl:18:1: The pattern <<X:[]>> can never match the type any()
8+
bs_fail_constr.erl:21:1: Function bad_size_2/1 has no local return
9+
bs_fail_constr.erl:24:9: The pattern <<X:Size>> can never match the type any()
610
bs_fail_constr.erl:5:1: Function w1/1 has no local return
711
bs_fail_constr.erl:6:5: Binary construction will fail since the value field V in segment V has type float()
812
bs_fail_constr.erl:8:1: Function w2/1 has no local return

lib/dialyzer/test/small_SUITE_data/src/bs_fail_constr.erl

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
-module(bs_fail_constr).
22

3-
-export([w1/1, w2/1, w3/1, w4/1]).
3+
-export([w1/1, w2/1, w3/1, w4/1, bad_size_1/1, bad_size_2/1]).
44

55
w1(V) when is_float(V) ->
66
<<V/integer>>.
@@ -13,3 +13,14 @@ w3(S) when is_integer(S), S < 0 ->
1313

1414
w4(V) when is_float(V) ->
1515
<<V/utf32>>.
16+
17+
%% GH-6419
18+
bad_size_1(<<X:[]>>) ->
19+
ok.
20+
21+
bad_size_2(Bin) ->
22+
Size = [],
23+
case Bin of
24+
<<X:Size>> ->
25+
ok
26+
end.

0 commit comments

Comments
 (0)