Skip to content

Commit 37d36f8

Browse files
committed
Do not expand bind_quoted expressions twice
1 parent 92e0e34 commit 37d36f8

File tree

3 files changed

+40
-24
lines changed

3 files changed

+40
-24
lines changed

lib/elixir/src/elixir_expand.erl

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -207,9 +207,14 @@ expand({quote, Meta, [Opts, Do]}, S, E) when is_list(Do) ->
207207
Unquote = proplists:get_value(unquote, EOpts, DefaultUnquote),
208208
Generated = proplists:get_value(generated, EOpts, false),
209209

210-
{Q, Prelude} = elixir_quote:build(Meta, Line, File, Context, Unquote, Generated, ET),
211-
Quoted = elixir_quote:quote(Meta, Exprs, Binding, Q, Prelude),
212-
expand(Quoted, ST, ET);
210+
{Q, EBinding, Prelude} = elixir_quote:build(Meta, Line, File, Context, Unquote, Generated, Binding, ET),
211+
Quoted = elixir_quote:quote(Exprs, Q, Prelude),
212+
{EQuoted, ES, EQ} = expand(Quoted, ST, ET),
213+
214+
case EBinding of
215+
[] -> {EQuoted, ES, EQ};
216+
_ -> {{'{}', [], ['__block__', [], EBinding ++ [EQuoted]]}, ES, EQ}
217+
end;
213218

214219
expand({quote, Meta, [_, _]}, _S, E) ->
215220
file_error(Meta, E, ?MODULE, {invalid_args, 'quote'});

lib/elixir/src/elixir_quote.erl

Lines changed: 15 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
-module(elixir_quote).
2-
-export([escape/3, linify/3, linify_with_context_counter/3, build/7, quote/5, has_unquotes/1, fun_to_quoted/1]).
2+
-export([escape/3, linify/3, linify_with_context_counter/3, build/8, quote/3, has_unquotes/1, fun_to_quoted/1]).
33
-export([dot/5, tail_list/3, list/2, validate_runtime/2]). %% Quote callbacks
44

55
-include("elixir.hrl").
@@ -200,7 +200,7 @@ bad_escape(Arg) ->
200200

201201
%% Quote entry points
202202

203-
build(Meta, Line, File, Context, Unquote, Generated, E) ->
203+
build(Meta, Line, File, Context, Unquote, Generated, Binding, E) ->
204204
Acc0 = [],
205205
{ELine, Acc1} = validate_compile(Meta, line, Line, Acc0),
206206
{EFile, Acc2} = validate_compile(Meta, file, File, Acc1),
@@ -219,7 +219,15 @@ build(Meta, Line, File, Context, Unquote, Generated, E) ->
219219
generated=Generated
220220
},
221221

222-
{Q, Acc3}.
222+
Vars =
223+
[{'{}', [],
224+
['=', [], [
225+
{'{}', [], [K, Meta, EContext]},
226+
V
227+
]
228+
]} || {K, V} <- Binding],
229+
230+
{Q, Vars, Acc3}.
223231

224232
validate_compile(_Meta, line, Value, Acc) when is_boolean(Value) ->
225233
{Value, Acc};
@@ -255,30 +263,16 @@ is_valid(context, Context) -> is_atom(Context) andalso (Context /= nil);
255263
is_valid(generated, Generated) -> is_boolean(Generated);
256264
is_valid(unquote, Unquote) -> is_boolean(Unquote).
257265

258-
quote(_Meta, {unquote_splicing, _, [_]}, _Binding, #elixir_quote{unquote=true}, _) ->
266+
quote({unquote_splicing, _, [_]}, #elixir_quote{unquote=true}, _) ->
259267
argument_error(<<"unquote_splicing only works inside arguments and block contexts, "
260268
"wrap it in parens if you want it to work with one-liners">>);
261269

262-
quote(Meta, Expr, Binding, Q, Prelude) ->
263-
Context = Q#elixir_quote.context,
264-
265-
Vars = [{'{}', [],
266-
['=', [], [
267-
{'{}', [], [K, Meta, Context]},
268-
V
269-
]]
270-
} || {K, V} <- Binding],
271-
270+
quote(Expr, Q, Prelude) ->
272271
Quoted = do_quote(Expr, Q),
273272

274-
WithVars = case Vars of
275-
[] -> Quoted;
276-
_ -> {'{}', [], ['__block__', [], Vars ++ [Quoted]]}
277-
end,
278-
279273
case Prelude of
280-
[] -> WithVars;
281-
_ -> {'__block__', [], Prelude ++ [WithVars]}
274+
[] -> Quoted;
275+
_ -> {'__block__', [], Prelude ++ [Quoted]}
282276
end.
283277

284278
%% quote/unquote

lib/elixir/test/elixir/kernel/expansion_test.exs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -621,6 +621,23 @@ defmodule Kernel.ExpansionTest do
621621
assert expand(quote(do: quote(do: hello)), []) == {:{}, [], [:hello, [], __MODULE__]}
622622
end
623623

624+
test "expand bind_quoted once" do
625+
expand_env(
626+
quote do
627+
var = 123
628+
quote(bind_quoted: [var: var], do: var)
629+
end,
630+
__ENV__,
631+
[]
632+
)
633+
|> elem(0)
634+
|> Macro.prewalk(fn
635+
{:var, [version: 0], Kernel.ExpansionTest} -> :ok
636+
{:var, _, Kernel.ExpansionTest} = invalid -> flunk("unexpected node #{inspect(invalid)}")
637+
node -> node
638+
end)
639+
end
640+
624641
test "raises if the :bind_quoted option is invalid" do
625642
assert_compile_error(~r"invalid :bind_quoted for quote", fn ->
626643
expand(quote(do: quote(bind_quoted: self(), do: :ok)))

0 commit comments

Comments
 (0)