Skip to content

Commit 9ea5085

Browse files
committed
Auto infer size of matched variable in bitstrings
1 parent a6b21f5 commit 9ea5085

File tree

2 files changed

+26
-6
lines changed

2 files changed

+26
-6
lines changed

lib/elixir/src/elixir_bitstring.erl

Lines changed: 16 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -33,12 +33,22 @@ expand(_BitstrMeta, _Fun, [], Acc, S, E, Alignment, _RequireSize) ->
3333
expand(BitstrMeta, Fun, [{'::', Meta, [Left, Right]} | T], Acc, S, E, Alignment, RequireSize) ->
3434
{ELeft, {SL, OriginalS}, EL} = expand_expr(Meta, Left, Fun, S, E),
3535

36-
MatchOrRequireSize = RequireSize or is_match_size(T, EL),
37-
EType = expr_type(ELeft),
38-
{ERight, EAlignment, SS, ES} = expand_specs(EType, Meta, Right, SL, OriginalS, EL, MatchOrRequireSize),
39-
40-
EAcc = concat_or_prepend_bitstring(Meta, ELeft, ERight, Acc, ES, MatchOrRequireSize),
41-
expand(BitstrMeta, Fun, T, EAcc, {SS, OriginalS}, ES, alignment(Alignment, EAlignment), RequireSize);
36+
case {ELeft, Right} of
37+
{{'^', _, [{var, _, _}]}, {Type, _, _}} when Type == binary; Type == bitstring ->
38+
SizeFun = case Type of
39+
binary -> byte_size;
40+
bitstring -> bit_size
41+
end,
42+
ERight = {'-', Meta, [Right, {size, Meta, [{{'.', Meta, [erlang, SizeFun]}, Meta, [ELeft]}]}]},
43+
EAcc = concat_or_prepend_bitstring(Meta, ELeft, ERight, Acc, EL, RequireSize),
44+
expand(BitstrMeta, Fun, T, EAcc, {SL, OriginalS}, EL, unknown, RequireSize);
45+
_ ->
46+
MatchOrRequireSize = RequireSize or is_match_size(T, EL),
47+
EType = expr_type(ELeft),
48+
{ERight, EAlignment, SS, ES} = expand_specs(EType, Meta, Right, SL, OriginalS, EL, MatchOrRequireSize),
49+
EAcc = concat_or_prepend_bitstring(Meta, ELeft, ERight, Acc, ES, MatchOrRequireSize),
50+
expand(BitstrMeta, Fun, T, EAcc, {SS, OriginalS}, ES, alignment(Alignment, EAlignment), RequireSize)
51+
end;
4252
expand(BitstrMeta, Fun, [H | T], Acc, S, E, Alignment, RequireSize) ->
4353
Meta = extract_meta(H, BitstrMeta),
4454
{ELeft, {SS, OriginalS}, ES} = expand_expr(Meta, H, Fun, S, E),

lib/elixir/test/elixir/kernel/binary_test.exs

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -269,6 +269,16 @@ defmodule Kernel.BinaryTest do
269269
assert <<1::size((^foo).bar)>> = <<1::5>>
270270
end
271271

272+
test "automatic size computation of matched bitsyntax variable" do
273+
var = "foo"
274+
<<^var::binary, rest::binary>> = "foobar"
275+
assert rest == "bar"
276+
277+
var = <<0, 1>>
278+
<<^var::bitstring, rest::bitstring>> = <<0, 1, 2, 3>>
279+
assert rest == <<2, 3>>
280+
end
281+
272282
defmacro signed_16 do
273283
quote do
274284
big - signed - integer - unit(16)

0 commit comments

Comments
 (0)