Skip to content

Commit 96a103d

Browse files
author
José Valim
committed
Allow :binding as an option in quote
This commit also adds Macro.expand_once/2 and Macro.expand_all/2.
1 parent f525f5b commit 96a103d

File tree

11 files changed

+318
-149
lines changed

11 files changed

+318
-149
lines changed

CHANGELOG.md

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77
* [Kernel] Warn on undefined module attributes
88
* [Kernel] Emit warning for 'x in []' in guards
99
* [Kernel] Add `binding/0` and `binding/1` for retrieving bindings
10+
* [Kernel] `quote` now allows a binding as an option
11+
* [Macro] Add `Macro.expand_once/2` and `Macro.expand_all/2`
1012
* [Mix] Implement `Mix.Version` for basic versioniong semantics
1113
* [Mix] Support creation and installation of archives (.ez files)
1214
* [Mix] `github: ...` shortcut now uses the faster `git` schema instead of `https`
@@ -30,6 +32,7 @@
3032
* [Bitwise] Precedence of operators used by the Bitwise module were changed. Check `elixir_parser.yrl` for more information.
3133
* [File] `rm_rf` and `cp_r` now returns a tuple with three elements on failures
3234
* [Kernel] The quoted representation for `->` clauses changed from a tuple with two elements to a tuple with three elements to support metadata
35+
* [Macro] `Macro.expand/2` now expands until final form. Although this is backwards incompatible, it is **very** likely your code should expand the node until its final form, particularly if you are expecting an atom out of it
3336
* [Mix] No longer support beam files on `mix local`
3437

3538
# v0.9.2 (2013-06-13)

lib/elixir/lib/kernel/special_forms.ex

Lines changed: 75 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -388,6 +388,8 @@ defmodule Kernel.SpecialForms do
388388
Read the Stacktrace information section below for more information;
389389
* `:hygiene` - Allows a developer to disable hygiene selectively;
390390
* `:context` - Sets the context resolution happens at;
391+
* `:binding` - Passes a binding to the macro. Whenever a binding is given,
392+
unquote is automatically disabled;
391393
392394
## Macro literals
393395
@@ -629,6 +631,79 @@ defmodule Kernel.SpecialForms do
629631
code as if it was defined inside `GenServer.Behaviour` file, in
630632
particular, the macro `__FILE__` and exceptions happening inside
631633
the quote will always point to `GenServer.Behaviour` file.
634+
635+
## Binding and unquote fragments
636+
637+
Elixir quote/unquote mechanisms provides a functionality called
638+
unquote fragments. Unquote fragments provide an easy to generate
639+
functions on the fly. Consider this example:
640+
641+
kv = [foo: 1, bar: 2]
642+
Enum.each kv, fn { k, v } ->
643+
def unquote(k)(), do: unquote(v)
644+
end
645+
646+
In the example above, we have generated the function `foo/0` and
647+
`bar/0` dynamically. Now, imagine that, we want to convert this
648+
functionality into a macro:
649+
650+
defmacro defkv(kv) do
651+
Enum.each kv, fn { k, v } ->
652+
quote do
653+
def unquote(k)(), do: unquote(v)
654+
end
655+
end
656+
end
657+
658+
We can invoke this macro as:
659+
660+
defkv [foo: 1, bar: 2]
661+
662+
However, we can't invoke it as follows:
663+
664+
kv = [foo: 1, bar: 2]
665+
defkv kv
666+
667+
This is because the macro is expecting its arguments to be a
668+
key-value at **compilation** time. Since in the example above
669+
we are passing the representation of the variable `kv`, our
670+
code fails.
671+
672+
This is actually a common pitfall when developing macros. In
673+
practive, we want to avoid doing work at compilation time as
674+
much as we can. That said, let's attempt to improve our macro:
675+
676+
defmacro defkv(kv) do
677+
quote do
678+
Enum.each unquote(kv), fn { k, v } ->
679+
def unquote(k)(), do: unquote(v)
680+
end
681+
end
682+
end
683+
684+
If you try to run our new macro, you will notice it won't
685+
even compile, complaining that the variables `k` and `v`
686+
do not exist. This is because of the ambiguity: `unquote(k)`
687+
can either be an unquote fragment, as previously, or a regular
688+
unquote as in `unquote(kv)`.
689+
690+
One solution for this problem is to disable unquoting in the
691+
macro, however, doing that would make it impossible to inject
692+
`kv` representation into the tree. That's when the `:binding`
693+
option comes to the rescue. By using `:binding`, we can
694+
automatically disable unquoting while still injecting the
695+
desired variables into the tree:
696+
697+
defmacro defkv(kv) do
698+
quote binding: [kv: kv] do
699+
Enum.each kv, fn { k, v } ->
700+
def unquote(k)(), do: unquote(v)
701+
end
702+
end
703+
end
704+
705+
In fact, the `:binding` option is recommended every time one
706+
desires to inject a value into the quote.
632707
"""
633708
defmacro quote(opts, block)
634709

lib/elixir/lib/macro.ex

Lines changed: 98 additions & 47 deletions
Original file line numberDiff line numberDiff line change
@@ -365,31 +365,18 @@ defmodule Macro do
365365
end
366366

367367
@doc """
368-
Receives an expression representation and expands it. The following
369-
contents are expanded:
368+
Receives a AST node and expands it once. The following contents are expanded:
370369
371370
* Macros (local or remote);
372371
* Aliases are expanded (if possible) and return atoms;
373372
* All pseudo-variables (__FILE__, __MODULE__, etc);
374373
* Module attributes reader (@foo);
375374
376-
In case the expression cannot be expanded, it returns the expression itself.
377-
378-
Notice that `Macro.expand` is not recursive and it does not
379-
expand child expressions. In this example:
380-
381-
Macro.expand(quote(do: var && some_macro), __ENV__)
382-
383-
`var && some_macro` will expand to something like:
384-
385-
case var do
386-
_ in [false, nil] -> var
387-
_ -> some_macro
388-
end
389-
390-
Notice that the `&&` operator is a macro that expands to a case.
391-
Even though `some_macro` is also a macro, it is not expanded
392-
because it is a child expression given to `&&` as argument.
375+
In case the expression cannot be expanded, it returns the expression
376+
itself. Notice that `Macro.expand_once/2` performs the expansion just
377+
once and it is not recursive. Check `Macro.expand/2` for expansion
378+
until the node no longer represents a macro and `Macro.expand_all/2`
379+
for recursive expansion.
393380
394381
## Examples
395382
@@ -452,46 +439,50 @@ defmodule Macro do
452439
end
453440
454441
"""
455-
def expand(aliases, env) do
456-
expand(aliases, env, nil)
442+
def expand_once(aliases, env) do
443+
expand_once(aliases, env, nil) |> elem(0)
457444
end
458445

459-
defp expand({ :__aliases__, _, _ } = original, env, cache) do
446+
defp expand_once({ :__aliases__, _, _ } = original, env, cache) do
460447
case :elixir_aliases.expand(original, env.aliases, env.macro_aliases) do
461-
atom when is_atom(atom) -> atom
448+
atom when is_atom(atom) -> { atom, true, cache }
462449
aliases ->
463-
aliases = lc alias inlist aliases, do: expand(alias, env, cache)
450+
aliases = lc alias inlist aliases, do: (expand_once(alias, env, cache) |> elem(0))
464451

465452
case :lists.all(is_atom(&1), aliases) do
466-
true -> :elixir_aliases.concat(aliases)
467-
false -> original
453+
true -> { :elixir_aliases.concat(aliases), true, cache }
454+
false -> { original, false, cache }
468455
end
469456
end
470457
end
471458

472459
# Expand @ calls
473-
defp expand({ :@, _, [{ name, _, args }] } = original, env, _cache) when is_atom(args) or args == [] do
460+
defp expand_once({ :@, _, [{ name, _, args }] } = original, env, cache) when is_atom(args) or args == [] do
474461
case (module = env.module) && Module.open?(module) do
475-
true -> Module.get_attribute(module, name)
476-
false -> original
462+
true -> { Module.get_attribute(module, name), true, cache }
463+
false -> { original, false, cache }
477464
end
478465
end
479466

480467
# Expand pseudo-variables
481-
defp expand({ :__MODULE__, _, atom }, env, _cache) when is_atom(atom), do: env.module
482-
defp expand({ :__FILE__, _, atom }, env, _cache) when is_atom(atom), do: env.file
483-
defp expand({ :__DIR__, _, atom }, env, _cache) when is_atom(atom), do: :filename.dirname(env.file)
484-
defp expand({ :__ENV__, _, atom }, env, _cache) when is_atom(atom), do: env
468+
defp expand_once({ :__MODULE__, _, atom }, env, cache) when is_atom(atom),
469+
do: { env.module, true, cache }
470+
defp expand_once({ :__FILE__, _, atom }, env, cache) when is_atom(atom),
471+
do: { env.file, true, cache }
472+
defp expand_once({ :__DIR__, _, atom }, env, cache) when is_atom(atom),
473+
do: { :filename.dirname(env.file), true, cache }
474+
defp expand_once({ :__ENV__, _, atom }, env, cache) when is_atom(atom),
475+
do: { env, true, cache }
485476

486477
# Expand possible macro import invocation
487-
defp expand({ atom, line, args } = original, env, cache) when is_atom(atom) do
478+
defp expand_once({ atom, line, args } = original, env, cache) when is_atom(atom) do
488479
args = case is_atom(args) do
489480
true -> []
490481
false -> args
491482
end
492483

493484
case not is_partial?(args) do
494-
false -> original
485+
false -> { original, false, cache }
495486
true ->
496487
module = env.module
497488

@@ -501,43 +492,103 @@ defmodule Macro do
501492
[]
502493
end
503494

495+
cache = to_erl_env(env, cache)
504496
expand = :elixir_dispatch.expand_import(line, { atom, length(args) }, args,
505-
env.module, extra, to_erl_env(env, cache))
497+
env.module, extra, cache)
498+
506499
case expand do
507-
{ :ok, _, expanded } -> expanded
508-
{ :error, _ } -> original
500+
{ :ok, _, expanded } -> { expanded, true, cache }
501+
{ :error, _ } -> { original, false, cache }
509502
end
510503
end
511504
end
512505

513506
# Expand possible macro require invocation
514-
defp expand({ { :., _, [left, right] }, line, args } = original, env, cache) when is_atom(right) do
515-
receiver = expand(left, env)
507+
defp expand_once({ { :., _, [left, right] }, line, args } = original, env, cache) when is_atom(right) do
508+
{ receiver, _, _ } = expand_once(left, env, cache)
516509

517510
case is_atom(receiver) and not is_partial?(args) do
518-
false -> original
511+
false -> { original, false, cache }
519512
true ->
513+
cache = to_erl_env(env, cache)
520514
expand = :elixir_dispatch.expand_require(line, receiver, { right, length(args) },
521-
args, env.module, to_erl_env(env, cache))
515+
args, env.module, cache)
516+
522517
case expand do
523-
{ :ok, _receiver, expanded } -> expanded
524-
{ :error, _ } -> original
518+
{ :ok, _receiver, expanded } -> { expanded, true, cache }
519+
{ :error, _ } -> { original, false, cache }
525520
end
526521
end
527522
end
528523

529524
# Anything else is just returned
530-
defp expand(other, _env, _cache), do: other
525+
defp expand_once(other, _env, cache), do: { other, false, cache }
531526

532527
defp to_erl_env(env, nil), do: :elixir_scope.to_erl_env(env)
533528
defp to_erl_env(_env, cache), do: cache
534529

535-
## Helpers
536-
537530
defp is_partial?(args) do
538531
:lists.any(match?({ :&, _, [_] }, &1), args)
539532
end
540533

534+
@doc """
535+
Receives a AST node and expands it until it no longer represents
536+
a macro. Check `Macro.expand_once/2` for more information on how
537+
expansion works and `Macro.expand_all/2` for recursive expansion.
538+
"""
539+
def expand(tree, env) do
540+
expand(tree, env, nil) |> elem(0)
541+
end
542+
543+
@doc false # Used internally by Elixir
544+
def expand(tree, env, cache) do
545+
expand_until({ tree, true, cache }, env)
546+
end
547+
548+
defp expand_until({ tree, true, cache }, env) do
549+
expand_until(expand_once(tree, env, cache), env)
550+
end
551+
552+
defp expand_until({ tree, false, cache }, _env) do
553+
{ tree, cache }
554+
end
555+
556+
@doc """
557+
Receives a AST node and expands it until it no longer represents
558+
a macro. Then it expands all of its children recursively.
559+
560+
Check `Macro.expand_once/2` for more information on how expansion
561+
works.
562+
"""
563+
def expand_all(tree, env) do
564+
expand_all(tree, env, nil) |> elem(0)
565+
end
566+
567+
@doc false # Used internally by Elixir
568+
def expand_all(tree, env, cache) do
569+
expand_all_until(expand(tree, env, cache), env)
570+
end
571+
572+
defp expand_all_until({ { left, meta, right }, cache }, env) do
573+
{ left, cache } = expand_all(left, env, cache)
574+
{ right, cache } = expand_all(right, env, cache)
575+
{ { left, meta, right }, cache }
576+
end
577+
578+
defp expand_all_until({ { left, right }, cache }, env) do
579+
{ left, cache } = expand_all(left, env, cache)
580+
{ right, cache } = expand_all(right, env, cache)
581+
{ { left, right }, cache }
582+
end
583+
584+
defp expand_all_until({ list, cache }, env) when is_list(list) do
585+
:lists.mapfoldl(expand_all(&1, env, &2), cache, list)
586+
end
587+
588+
defp expand_all_until({ other, cache }, _env) do
589+
{ other, cache }
590+
end
591+
541592
@doc """
542593
Recurs the quoted expression checking if all sub terms are
543594
safe (i.e. they represented data structured and don't actually

0 commit comments

Comments
 (0)