File 0777-compiler-Fix-skip-clause-for-binary-generators.patch of Package erlang
From 61bf34295452732ae347ea5d10556512d776a6a2 Mon Sep 17 00:00:00 2001
From: lucioleKi <isabell@erlang.org>
Date: Tue, 22 Oct 2024 13:16:30 +0200
Subject: [PATCH] compiler: Fix skip clause for binary generators
When the pattern in a binary generator is of the form `X:Y/float`, the
previous skip clause could never match. The skip pattern is changed
to `_:Y/integer`, so that it can match as long as `Y` is valid.
Before:
1> BadFloat = <<-1:64>>, [X || <<X:64/float>> <= <<BadFloat/binary, 1.0:64/float>>].
[]
Now:
1> BadFloat = <<-1:64>>, [X || <<X:64/float>> <= <<BadFloat/binary, 1.0:64/float>>].
[1.0]
---
lib/compiler/src/v3_core.erl | 8 ++++++++
lib/compiler/test/bs_bincomp_SUITE.erl | 13 +++++++++++--
lib/debugger/test/bs_bincomp_SUITE.erl | 13 +++++++++++--
lib/stdlib/src/eval_bits.erl | 17 +++++++++++++++++
lib/stdlib/test/erl_eval_SUITE.erl | 17 +++++++++++++++--
5 files changed, 62 insertions(+), 6 deletions(-)
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index e0fdc16de3..e315f6c7ef 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -1986,6 +1986,14 @@ append_tail_segment(Segs, St0) ->
%% in the skip clause that will continue the iteration when
%% the accumulator pattern didn't match.
+skip_segments([#ibitstr{val=#c_var{},type=#c_literal{val=float}}=B|Rest], St, Acc) ->
+ skip_segments(Rest, St, [B#ibitstr{type=#c_literal{val=integer}}|Acc]);
+skip_segments([#ibitstr{type=#c_literal{val=float}}=B|Rest], St0, Acc) ->
+ %% If the binary pattern has the form X:Y/float, the generated skip
+ %% clause is _:Y/integer, so that we skip as long as Y is valid.
+ {Var,St1} = new_var(St0),
+ B1 = B#ibitstr{val=Var,type=#c_literal{val=integer}},
+ skip_segments(Rest, St1, [B1|Acc]);
skip_segments([#ibitstr{val=#c_var{}}=B|Rest], St, Acc) ->
%% We must keep the names of existing variables to ensure that
%% patterns such as <<Size,X:Size>> will work.
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index 3d95ec29d8..4e4813eec2 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -27,7 +27,8 @@
byte_aligned/1,bit_aligned/1,extended_byte_aligned/1,
extended_bit_aligned/1,mixed/1,filters/1,trim_coverage/1,
nomatch/1,sizes/1,general_expressions/1,
- no_generator/1,zero_pattern/1,multiple_segments/1]).
+ no_generator/1,zero_pattern/1,multiple_segments/1,
+ float_skip/1]).
-include_lib("common_test/include/ct.hrl").
@@ -37,7 +38,8 @@ all() ->
[byte_aligned, bit_aligned, extended_byte_aligned,
extended_bit_aligned, mixed, filters, trim_coverage,
nomatch, sizes, general_expressions,
- no_generator, zero_pattern, multiple_segments].
+ no_generator, zero_pattern, multiple_segments,
+ float_skip].
groups() ->
[].
@@ -720,4 +720,13 @@ cs_default(Bin) ->
erts_debug:get_internal_state({binary_info,Bin}),
Bin.
+float_skip(Config) when is_list(Config) ->
+ BadFloat = <<-1:64>>,
+ [1.0,1.5,200.0] = [X || <<X:64/float>> <= <<BadFloat/binary,
+ 1:64/float, 1.5:64/float, 200:64/float>>],
+ [24.0,+48.5,21.0] =[X || <<X:64/float>> <= <<24:64/float,
+ BadFloat/binary, 48.5:64/float, 21:64/float>>],
+ [a,a] =[a || <<0:64/float>> <= <<0:64/float, BadFloat/binary,
+ 0:64/float, 1.0:64/float>>].
+
id(I) -> I.
diff --git a/lib/debugger/test/bs_bincomp_SUITE.erl b/lib/debugger/test/bs_bincomp_SUITE.erl
index 064e9567b3..fd0223ce83 100644
--- a/lib/debugger/test/bs_bincomp_SUITE.erl
+++ b/lib/debugger/test/bs_bincomp_SUITE.erl
@@ -28,7 +28,7 @@
init_per_group/2,end_per_group/2,
init_per_testcase/2,end_per_testcase/2,
byte_aligned/1,bit_aligned/1,extended_byte_aligned/1,
- extended_bit_aligned/1,mixed/1]).
+ extended_bit_aligned/1,mixed/1,float_skip/1]).
-include_lib("common_test/include/ct.hrl").
@@ -45,7 +45,7 @@ suite() ->
all() ->
[byte_aligned, bit_aligned, extended_byte_aligned,
- extended_bit_aligned, mixed].
+ extended_bit_aligned, mixed, float_skip].
groups() ->
[].
@@ -125,3 +125,12 @@ mixed(Config) when is_list(Config) ->
[2,3,3,4,4,5,5,6] =
[(X+Y) || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, Y <- [1,2]],
ok.
+
+float_skip(Config) when is_list(Config) ->
+ BadFloat = <<-1:64>>,
+ [1.0,1.5,200.0] = [X || <<X:64/float>> <= <<BadFloat/binary,
+ 1:64/float, 1.5:64/float, 200:64/float>>],
+ [24.0,+48.5,21.0] =[X || <<X:64/float>> <= <<24:64/float,
+ BadFloat/binary, 48.5:64/float, 21:64/float>>],
+ [a,a] =[a || <<0:64/float>> <= <<0:64/float, BadFloat/binary,
+ 0:64/float, 1.0:64/float>>].
\ No newline at end of file
diff --git a/lib/stdlib/src/eval_bits.erl b/lib/stdlib/src/eval_bits.erl
index ccd144ad71..ca80451949 100644
--- a/lib/stdlib/src/eval_bits.erl
+++ b/lib/stdlib/src/eval_bits.erl
@@ -258,6 +258,23 @@ bin_gen_field_string([C|Cs], Bin0, Bs0, BBs0, Fun) ->
done
end.
+bin_gen_field1(Bin, float, Size, Unit, Sign, Endian, NewV, Bs0, BBs0, Mfun) ->
+ case catch get_value(Bin, float, Size, Unit, Sign, Endian) of
+ {Val,<<_/bitstring>>=Rest} ->
+ case catch Mfun(match, {NewV,Val,Bs0}) of
+ {match,Bs} ->
+ BBs = add_bin_binding(Mfun, NewV, Bs, BBs0),
+ {match,Bs,BBs,Rest};
+ _ ->
+ {nomatch,Rest}
+ end;
+ _ ->
+ case catch get_value(Bin, integer, Size, Unit, Sign, Endian) of
+ {_,<<_/bitstring>>=Rest} ->
+ {nomatch,Rest};
+ _ -> done
+ end
+ end;
bin_gen_field1(Bin, Type, Size, Unit, Sign, Endian, NewV, Bs0, BBs0, Mfun) ->
case catch get_value(Bin, Type, Size, Unit, Sign, Endian) of
{Val,<<_/bitstring>>=Rest} ->
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index e28dd788bb..2748a0977f 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -55,7 +55,8 @@
otp_14708/1,
otp_16545/1,
otp_16865/1,
- eep49/1]).
+ eep49/1,
+ binary_skip/1]).
%%
%% Define to run outside of test server
@@ -97,7 +98,7 @@ all() ->
otp_8133, otp_10622, otp_13228, otp_14826,
funs, custom_stacktrace, try_catch, eval_expr_5, zero_width,
eep37, eep43, otp_15035, otp_16439, otp_14708, otp_16545, otp_16865,
- eep49].
+ eep49, binary_skip].
groups() ->
[].
@@ -1997,6 +1998,18 @@ eep49(Config) when is_list(Config) ->
{else_clause,simply_wrong}),
ok.
+binary_skip(Config) when is_list(Config) ->
+ check(fun() -> X = 32, [X || <<X:64/float>> <= <<-1:64, 0:64, 0:64, 0:64>>] end,
+ "begin X = 32, [X || <<X:64/float>> <= <<-1:64, 0:64, 0:64, 0:64>>] end.",
+ [+0.0,+0.0,+0.0]),
+ check(fun() -> X = 32, [X || <<X:64/float>> <= <<0:64, -1:64, 0:64, 0:64>>] end,
+ "begin X = 32, [X || <<X:64/float>> <= <<0:64, -1:64, 0:64, 0:64>>] end.",
+ [+0.0,+0.0,+0.0]),
+ check(fun() -> [a || <<0:64/float>> <= <<0:64, 1:64, 0:64, 0:64>> ] end,
+ "begin [a || <<0:64/float>> <= <<0:64, 1:64, 0:64, 0:64>> ] end.",
+ [a,a,a]),
+ ok.
+
%% Check the string in different contexts: as is; in fun; from compiled code.
check(F, String, Result) ->
check1(F, String, Result),
--
2.43.0