Skip to content

Commit 38baa72

Browse files
author
José Valim
committed
Annotate the context for variables as zero-arity funs in quotes
Signed-off-by: José Valim <jose.valim@plataformatec.com.br>
1 parent 5fe53f7 commit 38baa72

File tree

2 files changed

+47
-24
lines changed

2 files changed

+47
-24
lines changed

lib/elixir/src/elixir_quote.erl

Lines changed: 33 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -189,12 +189,15 @@ do_quote({'__aliases__', Meta, [H | T]} = Alias, #elixir_quote{aliases_hygiene=t
189189
Aliases when is_list(Aliases) -> false
190190
end,
191191
AliasMeta = keystore(alias, keydelete(counter, Meta), Annotation),
192-
do_quote_tuple({'__aliases__', AliasMeta, [H | T]}, Q, E);
192+
do_quote_tuple('__aliases__', AliasMeta, [H | T], Q, E);
193193

194194
%% Vars
195195

196+
do_quote({Left, Meta, nil}, #elixir_quote{vars_hygiene=true, imports_hygiene=true} = Q, E) when is_atom(Left) ->
197+
do_quote_import(Left, Meta, Q#elixir_quote.context, Q, E);
198+
196199
do_quote({Left, Meta, nil}, #elixir_quote{vars_hygiene=true} = Q, E) when is_atom(Left) ->
197-
do_quote_tuple({Left, Meta, Q#elixir_quote.context}, Q, E);
200+
do_quote_tuple(Left, Meta, Q#elixir_quote.context, Q, E);
198201

199202
%% Unquote
200203

@@ -207,28 +210,11 @@ do_quote({{'.', Meta, [Left, unquote]}, _, [Expr]}, #elixir_quote{unquote=true}
207210
%% Imports
208211

209212
do_quote({'&', Meta, [{'/', _, [{F, _, C}, A]}] = Args},
210-
#elixir_quote{imports_hygiene=true} = Q, E) when is_atom(F), is_integer(A), is_atom(C) ->
213+
#elixir_quote{imports_hygiene=true} = Q, E) when is_atom(F), is_integer(A), is_atom(C) ->
211214
do_quote_fa('&', Meta, Args, F, A, Q, E);
212215

213216
do_quote({Name, Meta, ArgsOrAtom}, #elixir_quote{imports_hygiene=true} = Q, E) when is_atom(Name) ->
214-
Arity = case is_atom(ArgsOrAtom) of
215-
true -> 0;
216-
false -> length(ArgsOrAtom)
217-
end,
218-
219-
NewMeta = case (keyfind(import, Meta) == false) andalso
220-
elixir_dispatch:find_import(Meta, Name, Arity, E) of
221-
false ->
222-
case (Arity == 1) andalso keyfind(ambiguous_op, Meta) of
223-
{ambiguous_op, nil} -> keystore(ambiguous_op, Meta, Q#elixir_quote.context);
224-
_ -> Meta
225-
end;
226-
Receiver ->
227-
keystore(import, keystore(context, Meta, Q#elixir_quote.context), Receiver)
228-
end,
229-
230-
Annotated = annotate({Name, NewMeta, ArgsOrAtom}, Q#elixir_quote.context),
231-
do_quote_tuple(Annotated, Q, E);
217+
do_quote_import(Name, Meta, ArgsOrAtom, Q, E);
232218

233219
do_quote({_, _, _} = Tuple, #elixir_quote{escape=false} = Q, E) ->
234220
Annotated = annotate(Tuple, Q#elixir_quote.context),
@@ -300,6 +286,26 @@ bad_escape(Arg) ->
300286
"The supported values are: lists, tuples, maps, atoms, numbers, bitstrings, ",
301287
"PIDs and remote functions in the format &Mod.fun/arity">>).
302288

289+
do_quote_import(Name, Meta, ArgsOrAtom, #elixir_quote{imports_hygiene=true} = Q, E) ->
290+
Arity = case is_atom(ArgsOrAtom) of
291+
true -> 0;
292+
false -> length(ArgsOrAtom)
293+
end,
294+
295+
NewMeta = case (keyfind(import, Meta) == false) andalso
296+
elixir_dispatch:find_import(Meta, Name, Arity, E) of
297+
false ->
298+
case (Arity == 1) andalso keyfind(ambiguous_op, Meta) of
299+
{ambiguous_op, nil} -> keystore(ambiguous_op, Meta, Q#elixir_quote.context);
300+
_ -> Meta
301+
end;
302+
Receiver ->
303+
keystore(import, keystore(context, Meta, Q#elixir_quote.context), Receiver)
304+
end,
305+
306+
Annotated = annotate({Name, NewMeta, ArgsOrAtom}, Q#elixir_quote.context),
307+
do_quote_tuple(Annotated, Q, E).
308+
303309
do_quote_call(Left, Meta, Expr, Args, Q, E) ->
304310
All = [meta(Meta, Q), Left, {unquote, Meta, [Expr]}, Args,
305311
Q#elixir_quote.context],
@@ -313,21 +319,24 @@ do_quote_fa(Target, Meta, Args, F, A, Q, E) ->
313319
false -> Meta;
314320
Receiver -> keystore(import_fa, Meta, {Receiver, Q#elixir_quote.context})
315321
end,
316-
do_quote_tuple({Target, NewMeta, Args}, Q, E).
322+
do_quote_tuple(Target, NewMeta, Args, Q, E).
323+
324+
do_quote_tuple({Left, Meta, Right}, Q, E) ->
325+
do_quote_tuple(Left, Meta, Right, Q, E).
317326

318327
% In a def unquote(name)(args) expression name will be an atom literal,
319328
% thus location: :keep will not have enough information to generate the proper file/line annotation.
320329
% This alters metadata to force Elixir to show the file to which the definition is added
321330
% instead of the file where definition is quoted (i.e. we behave the opposite to location: :keep).
322-
do_quote_tuple({Left, Meta, [{{unquote, _, _}, _, _}, _] = Right}, Q, E) when ?defs(Left) ->
331+
do_quote_tuple(Left, Meta, [{{unquote, _, _}, _, _}, _] = Right, Q, E) when ?defs(Left) ->
323332
{TLeft, LQ} = do_quote(Left, Q, E),
324333
{[Head, Body], RQ} = do_quote(Right, LQ, E),
325334
{'{}', [], [HLeft, HMeta, HRight]} = Head,
326335
NewMeta = lists:keydelete(file, 1, HMeta),
327336
NewHead = {'{}', [], [HLeft, NewMeta, HRight]},
328337
{{'{}', [], [TLeft, meta(Meta, Q), [NewHead, Body]]}, RQ};
329338

330-
do_quote_tuple({Left, Meta, Right}, Q, E) ->
339+
do_quote_tuple(Left, Meta, Right, Q, E) ->
331340
{TLeft, LQ} = do_quote(Left, Q, E),
332341
{TRight, RQ} = do_quote(Right, LQ, E),
333342
{{'{}', [], [TLeft, meta(Meta, Q), TRight]}, RQ}.

lib/elixir/test/elixir/kernel/quote_test.exs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -434,4 +434,18 @@ defmodule Kernel.QuoteTest.ImportsHygieneTest do
434434
test "explicitly overridden imports" do
435435
assert with_length() == 5
436436
end
437+
438+
defmodule BinaryUtils do
439+
defmacro int32 do
440+
quote do
441+
integer-size(32)
442+
end
443+
end
444+
end
445+
446+
test "checks the context also for variables to zero-arity functions" do
447+
import BinaryUtils
448+
{:int32, meta, __MODULE__} = quote do: int32
449+
assert meta[:import] == BinaryUtils
450+
end
437451
end

0 commit comments

Comments
 (0)