Skip to content

Commit 54cabc4

Browse files
committed
Add local_for_callback option to expand_import
Allow hooking into local macro resolution
1 parent efcd164 commit 54cabc4

File tree

2 files changed

+43
-17
lines changed

2 files changed

+43
-17
lines changed

lib/elixir/lib/macro/env.ex

Lines changed: 22 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -98,7 +98,8 @@ defmodule Macro.Env do
9898
@type expand_import_opts :: [
9999
allow_locals: boolean(),
100100
check_deprecations: boolean(),
101-
trace: boolean()
101+
trace: boolean(),
102+
local_for_callback: (Macro.metadata(), atom(), arity(), [atom()], t() -> any())
102103
]
103104

104105
@type expand_require_opts :: [
@@ -561,6 +562,12 @@ defmodule Macro.Env do
561562
* `:check_deprecations` - when set to `false`, does not check for deprecations
562563
when expanding macros
563564
565+
* `:local_for_callback` - a function that receives the metadata, name, arity,
566+
kinds list, and environment, and returns the local macro expansion or `false`.
567+
The expansion can be a function or any other value. Non-function values will
568+
cause the macro expansion to be skipped and return `:ok`.
569+
Defaults to calling `:elixir_def.local_for/5`
570+
564571
* #{trace_option}
565572
566573
"""
@@ -571,6 +578,10 @@ defmodule Macro.Env do
571578
| {:error, :not_found | {:conflict, module()} | {:ambiguous, [module()]}}
572579
def expand_import(env, meta, name, arity, opts \\ [])
573580
when is_list(meta) and is_atom(name) and is_integer(arity) and is_list(opts) do
581+
local_for_callback = Keyword.get(opts, :local_for_callback, fn meta, name, arity, kinds, e ->
582+
:elixir_def.local_for(meta, name, arity, kinds, e)
583+
end)
584+
574585
case :elixir_import.special_form(name, arity) do
575586
true ->
576587
{:error, :not_found}
@@ -580,13 +591,19 @@ defmodule Macro.Env do
580591
trace = Keyword.get(opts, :trace, true)
581592
module = env.module
582593

594+
# When local_for_callback is provided, we don't need to pass module macros as extra
595+
# because the callback will handle local macro resolution
583596
extra =
584-
case allow_locals and function_exported?(module, :__info__, 1) do
585-
true -> [{module, module.__info__(:macros)}]
586-
false -> []
597+
if Keyword.has_key?(opts, :local_for_callback) do
598+
[]
599+
else
600+
case allow_locals and function_exported?(module, :__info__, 1) do
601+
true -> [{module, module.__info__(:macros)}]
602+
false -> []
603+
end
587604
end
588605

589-
case :elixir_dispatch.expand_import(meta, name, arity, env, extra, allow_locals, trace) do
606+
case :elixir_dispatch.expand_import(meta, name, arity, env, extra, allow_locals, trace, local_for_callback) do
590607
{:macro, receiver, expander} ->
591608
{:macro, receiver, wrap_expansion(receiver, expander, meta, name, arity, env, opts)}
592609

lib/elixir/src/elixir_dispatch.erl

Lines changed: 21 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88
-module(elixir_dispatch).
99
-export([dispatch_import/6, dispatch_require/7,
1010
require_function/5, import_function/4,
11-
expand_import/7, expand_require/6, check_deprecated/6,
11+
expand_import/8, expand_require/6, check_deprecated/6,
1212
default_functions/0, default_macros/0, default_requires/0,
1313
find_import/4, find_imports/3, format_error/1]).
1414
-include("elixir.hrl").
@@ -115,7 +115,8 @@ dispatch_import(Meta, Name, Args, S, E, Callback) ->
115115
_ -> false
116116
end,
117117

118-
case expand_import(Meta, Name, Arity, E, [], AllowLocals, true) of
118+
DefaultLocalForCallback = fun(M, N, A, K, Env) -> elixir_def:local_for(M, N, A, K, Env) end,
119+
case expand_import(Meta, Name, Arity, E, [], AllowLocals, true, DefaultLocalForCallback) of
119120
{macro, Receiver, Expander} ->
120121
check_deprecated(macro, Meta, Receiver, Name, Arity, E),
121122
Caller = {?line(Meta), S, E},
@@ -159,7 +160,7 @@ dispatch_require(_Meta, Receiver, Name, _Args, _S, _E, Callback) ->
159160

160161
%% Macros expansion
161162

162-
expand_import(Meta, Name, Arity, E, Extra, AllowLocals, Trace) ->
163+
expand_import(Meta, Name, Arity, E, Extra, AllowLocals, Trace, LocalForCallback) ->
163164
Tuple = {Name, Arity},
164165
Module = ?key(E, module),
165166
Dispatch = find_import_by_name_arity(Meta, Tuple, Extra, E),
@@ -172,7 +173,7 @@ expand_import(Meta, Name, Arity, E, Extra, AllowLocals, Trace) ->
172173
do_expand_import(Dispatch, Meta, Name, Arity, Module, E, Trace);
173174

174175
_ ->
175-
Local = AllowLocals andalso elixir_def:local_for(Meta, Name, Arity, [defmacro, defmacrop], E),
176+
Local = AllowLocals andalso LocalForCallback(Meta, Name, Arity, [defmacro, defmacrop], E),
176177

177178
case Dispatch of
178179
%% There is a local and an import. This is a conflict unless
@@ -249,14 +250,22 @@ expander_macro_named(Meta, Receiver, Name, Arity, E) ->
249250
fun(Args, Caller) -> expand_macro_fun(Meta, Fun, Receiver, Name, Args, Caller, E) end.
250251

251252
expand_macro_fun(Meta, Fun, Receiver, Name, Args, Caller, E) ->
252-
try
253-
apply(Fun, [Caller | Args])
254-
catch
255-
Kind:Reason:Stacktrace ->
256-
Arity = length(Args),
257-
MFA = {Receiver, elixir_utils:macro_name(Name), Arity+1},
258-
Info = [{Receiver, Name, Arity, [{file, "expanding macro"}]}, caller(?line(Meta), E)],
259-
erlang:raise(Kind, Reason, prune_stacktrace(Stacktrace, MFA, Info, {ok, Caller}))
253+
%% Check if Fun is actually a function, as it might be a fake value for local macros
254+
%% when using custom local_for_callback
255+
case is_function(Fun) of
256+
true ->
257+
try
258+
apply(Fun, [Caller | Args])
259+
catch
260+
Kind:Reason:Stacktrace ->
261+
Arity = length(Args),
262+
MFA = {Receiver, elixir_utils:macro_name(Name), Arity+1},
263+
Info = [{Receiver, Name, Arity, [{file, "expanding macro"}]}, caller(?line(Meta), E)],
264+
erlang:raise(Kind, Reason, prune_stacktrace(Stacktrace, MFA, Info, {ok, Caller}))
265+
end;
266+
false ->
267+
%% Return a fake value and omit expansion when Fun is not a function
268+
ok
260269
end.
261270

262271
expand_quoted(Meta, Receiver, Name, Arity, Quoted, S, E) ->

0 commit comments

Comments
 (0)