Skip to content

Commit 95377a3

Browse files
author
José Valim
committed
Expand macros and quoted variables inside << >>, closes #1063
1 parent 05c1630 commit 95377a3

File tree

2 files changed

+27
-28
lines changed

2 files changed

+27
-28
lines changed

lib/elixir/src/elixir_literal.erl

Lines changed: 19 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -96,37 +96,28 @@ build_bitstr_each(Fun, [{'::',_,[H,V]}|T], Meta, S, Acc) ->
9696
build_bitstr_each(Fun, [H|T], Meta, S, Acc) ->
9797
build_bitstr_each(Fun, T, Meta, S, Acc, H, default, default).
9898

99-
build_bitstr_each(Fun, T, Meta, S, Acc, H, Size, Types) when is_list(H) ->
100-
case is_default_or_utf(Types) of
101-
true ->
102-
{ NewAcc, NewS } = lists:foldl(fun(L, { LA, LS }) ->
103-
{ FL, FS } = Fun(L, LS),
104-
{ [{ bin_element, ?line(Meta), FL, Size, Types }|LA], FS }
105-
end, { Acc, S }, H),
106-
build_bitstr_each(Fun, T, Meta, NewS, NewAcc);
107-
false ->
108-
build_bitstr_default(Fun, T, Meta, S, Acc, H, Size, Types)
109-
end;
99+
build_bitstr_each(Fun, T, Meta, S, Acc, H, Size, Types) ->
100+
{ Expr, NS } = Fun(H, S),
101+
case (is_default_or_utf(Types) andalso Expr) of
102+
{ bin, _, BinElements } ->
103+
build_bitstr_each(Fun, T, Meta, NS, rehash_bin_elements(BinElements, Size, Types, []) ++ Acc);
104+
{ cons, _, _, _ } = Cons ->
105+
build_bitstr_each(Fun, T, Meta, NS, rehash_cons(Cons, Size, Types, []) ++ Acc);
106+
{ nil, _ } ->
107+
build_bitstr_each(Fun, T, Meta, NS, Acc);
108+
_ ->
109+
build_bitstr_each(Fun, T, Meta, NS, [{ bin_element, ?line(Meta), Expr, Size, Types }|Acc])
110+
end.
110111

111-
build_bitstr_each(Fun, T, Meta, S, Acc, H, Size, Types) when is_bitstring(H) ->
112-
case is_default_or_utf(Types) of
113-
true ->
114-
Line = ?line(Meta),
115-
{ bin, _, Elements } = elixir_tree_helpers:elixir_to_erl(H),
116-
NewAcc = lists:foldl(fun({ bin_element, _, Expr, _, _ }, FinalAcc) ->
117-
[{ bin_element, Line, Expr, Size, Types }|FinalAcc]
118-
end, Acc, Elements),
119-
build_bitstr_each(Fun, T, Meta, S, NewAcc);
120-
false ->
121-
build_bitstr_default(Fun, T, Meta, S, Acc, H, Size, Types)
122-
end;
112+
rehash_cons({ nil, _ }, _Size, _Types, Acc) -> Acc;
113+
rehash_cons({ cons, Line, Left, Right }, Size, Types, Acc) ->
114+
rehash_cons(Right, Size, Types, [{ bin_element, Line, Left, Size, Types }|Acc]).
123115

124-
build_bitstr_each(Fun, T, Meta, S, Acc, H, Size, Types) ->
125-
build_bitstr_default(Fun, T, Meta, S, Acc, H, Size, Types).
116+
rehash_bin_elements([{ bin_element, Line, Expr, _S, _T }|T], Size, Types, Acc) ->
117+
rehash_bin_elements(T, Size, Types, [{ bin_element, Line, Expr, Size, Types }|Acc]);
126118

127-
build_bitstr_default(Fun, T, Meta, S, Acc, H, Size, Types) ->
128-
{ Expr, NS } = Fun(H, S),
129-
build_bitstr_each(Fun, T, Meta, NS, [{ bin_element, ?line(Meta), Expr, Size, Types }|Acc]).
119+
rehash_bin_elements([], _Size, _Types, Acc) ->
120+
Acc.
130121

131122
is_default_or_utf(default) -> true;
132123
is_default_or_utf([UTF|_]) when UTF == utf8; UTF == utf16; UTF == utf32 -> true;

lib/elixir/test/elixir/binary_test.exs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -98,6 +98,14 @@ bar
9898
assert <<0,0,0,106,0,0,0,111,0,0,0,115,0,0,0,101>> == << 'jose' :: utf32 >>
9999
end
100100

101+
@binary "new "
102+
@charlist 'old '
103+
104+
test :bitsyntax_with_expansion do
105+
assert <<@binary, "world">> == "new world"
106+
assert <<@charlist, "world">> == "old world"
107+
end
108+
101109
test :bitsyntax_translation do
102110
refb = "sample"
103111
sec_data = "another"

0 commit comments

Comments
 (0)