Skip to content

Commit 5f2f626

Browse files
committed
Do not raise on Macro.Env.expand_import, closes #13573
1 parent 7e87e3f commit 5f2f626

File tree

4 files changed

+62
-39
lines changed

4 files changed

+62
-39
lines changed

lib/elixir/lib/macro.ex

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1871,8 +1871,11 @@ defmodule Macro do
18711871
{:function, _receiver, _name} ->
18721872
{original, false}
18731873

1874-
:error ->
1874+
{:error, :not_found} ->
18751875
{original, false}
1876+
1877+
{:error, other} ->
1878+
:elixir_errors.file_error(meta, env, :elixir_dispatch, {:import, other, name, arity})
18761879
end
18771880
end
18781881

lib/elixir/lib/macro/env.ex

Lines changed: 26 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -490,7 +490,7 @@ defmodule Macro.Env do
490490
If any import is found, the appropriate compiler tracing
491491
event will be emitted.
492492
493-
Otherwise returns `:error`.
493+
Otherwise returns `{:error, reason}`.
494494
495495
## Options
496496
@@ -507,12 +507,12 @@ defmodule Macro.Env do
507507
@spec expand_import(t, keyword, atom(), arity(), keyword) ::
508508
{:macro, module(), (Macro.metadata(), args :: [Macro.t()] -> Macro.t())}
509509
| {:function, module(), atom()}
510-
| :error
510+
| {:error, :not_found | {:conflict, module()} | {:ambiguous, [module()]}}
511511
def expand_import(env, meta, name, arity, opts \\ [])
512512
when is_list(meta) and is_atom(name) and is_integer(arity) and is_list(opts) do
513513
case :elixir_import.special_form(name, arity) do
514514
true ->
515-
:error
515+
{:error, :not_found}
516516

517517
false ->
518518
allow_locals = Keyword.get(opts, :allow_locals, true)
@@ -525,10 +525,16 @@ defmodule Macro.Env do
525525
false -> []
526526
end
527527

528-
result =
529-
:elixir_dispatch.expand_import(meta, name, arity, env, extra, allow_locals, trace)
528+
case :elixir_dispatch.expand_import(meta, name, arity, env, extra, allow_locals, trace) do
529+
{:macro, receiver, expander} ->
530+
{:macro, receiver, wrap_expansion(receiver, expander, meta, name, arity, env, opts)}
531+
532+
{:function, receiver, name} ->
533+
{:function, receiver, name}
530534

531-
wrap_expansion(result, meta, name, arity, env, opts)
535+
error ->
536+
{:error, error}
537+
end
532538
end
533539
end
534540

@@ -561,24 +567,10 @@ defmodule Macro.Env do
561567
when is_list(meta) and is_atom(module) and is_atom(name) and is_integer(arity) and
562568
is_list(opts) do
563569
trace = Keyword.get(opts, :trace, true)
564-
result = :elixir_dispatch.expand_require(meta, module, name, arity, env, trace)
565-
wrap_expansion(result, meta, name, arity, env, opts)
566-
end
567570

568-
defp wrap_expansion(result, meta, name, arity, env, opts) do
569-
case result do
571+
case :elixir_dispatch.expand_require(meta, module, name, arity, env, trace) do
570572
{:macro, receiver, expander} ->
571-
fun = fn expansion_meta, args ->
572-
if Keyword.get(opts, :check_deprecations, true) do
573-
:elixir_dispatch.check_deprecated(:macro, meta, receiver, name, arity, env)
574-
end
575-
576-
quoted = expander.(args, :elixir_env.env_to_ex(env))
577-
next = :elixir_module.next_counter(env.module)
578-
:elixir_quote.linify_with_context_counter(expansion_meta, {receiver, next}, quoted)
579-
end
580-
581-
{:macro, receiver, fun}
573+
{:macro, receiver, wrap_expansion(receiver, expander, meta, name, arity, env, opts)}
582574

583575
{:function, receiver, name} ->
584576
{:function, receiver, name}
@@ -588,6 +580,18 @@ defmodule Macro.Env do
588580
end
589581
end
590582

583+
defp wrap_expansion(receiver, expander, meta, name, arity, env, opts) do
584+
fn expansion_meta, args ->
585+
if Keyword.get(opts, :check_deprecations, true) do
586+
:elixir_dispatch.check_deprecated(:macro, meta, receiver, name, arity, env)
587+
end
588+
589+
quoted = expander.(args, :elixir_env.env_to_ex(env))
590+
next = :elixir_module.next_counter(env.module)
591+
:elixir_quote.linify_with_context_counter(expansion_meta, {receiver, next}, quoted)
592+
end
593+
end
594+
591595
@doc """
592596
Returns an environment in the guard context.
593597
"""

lib/elixir/src/elixir_dispatch.erl

Lines changed: 19 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,8 @@ find_import(Meta, Name, Arity, E) ->
3232
{macro, Receiver} ->
3333
elixir_env:trace({imported_macro, Meta, Receiver, Name, Arity}, E),
3434
Receiver;
35+
{ambiguous, _} = Ambiguous ->
36+
elixir_errors:file_error(Meta, E, ?MODULE, {import, Ambiguous, Name, Arity});
3537
_ ->
3638
false
3739
end.
@@ -75,6 +77,8 @@ import_function(Meta, Name, Arity, E) ->
7577
false;
7678
{import, Receiver} ->
7779
require_function(Meta, Receiver, Name, Arity, E);
80+
{ambiguous, Ambiguous} ->
81+
elixir_errors:file_error(Meta, E, ?MODULE, {import, Ambiguous, Name, Arity});
7882
false ->
7983
case elixir_import:special_form(Name, Arity) of
8084
true ->
@@ -130,8 +134,10 @@ dispatch_import(Meta, Name, Args, S, E, Callback) ->
130134
expand_quoted(Meta, Receiver, Name, Arity, Expander(Args, S), S, E);
131135
{function, Receiver, NewName} ->
132136
elixir_expand:expand({{'.', Meta, [Receiver, NewName]}, Meta, Args}, S, E);
133-
error ->
134-
Callback()
137+
not_found ->
138+
Callback();
139+
Error ->
140+
elixir_errors:file_error(Meta, E, ?MODULE, {import, Error, Name, Arity})
135141
end.
136142

137143
dispatch_require(Meta, Receiver, Name, Args, S, E, Callback) when is_atom(Receiver) ->
@@ -164,17 +170,20 @@ expand_import(Meta, Name, Arity, E, Extra, AllowLocals, Trace) ->
164170
Dispatch = find_import_by_name_arity(Meta, Tuple, Extra, E),
165171

166172
case Dispatch of
173+
{ambiguous, Ambiguous} ->
174+
{ambiguous, Ambiguous};
175+
167176
{import, _} ->
168177
do_expand_import(Dispatch, Meta, Name, Arity, Module, E, Trace);
178+
169179
_ ->
170180
Local = AllowLocals andalso elixir_def:local_for(Meta, Name, Arity, [defmacro, defmacrop], E),
171181

172182
case Dispatch of
173183
%% There is a local and an import. This is a conflict unless
174184
%% the receiver is the same as module (happens on bootstrap).
175185
{_, Receiver} when Local /= false, Receiver /= Module ->
176-
Error = {macro_conflict, {Receiver, Name, Arity}},
177-
elixir_errors:file_error(Meta, E, ?MODULE, Error);
186+
{conflict, Receiver};
178187

179188
%% There is no local. Dispatch the import.
180189
_ when Local == false ->
@@ -212,10 +221,10 @@ do_expand_import(Result, Meta, Name, Arity, Module, E, Trace) ->
212221
false when Module == ?kernel ->
213222
case elixir_rewrite:inline(Module, Name, Arity) of
214223
{AR, AN} -> {function, AR, AN};
215-
false -> error
224+
false -> not_found
216225
end;
217226
false ->
218-
error
227+
not_found
219228
end.
220229

221230
expand_require(Meta, Receiver, Name, Arity, E, Trace) ->
@@ -286,7 +295,7 @@ find_imports_by_name([], Acc, _Name, _Meta, _E) ->
286295
find_imports_by_name(Name, [{Name, Arity} | Imports], Acc, Mod, Meta, E) ->
287296
case Acc of
288297
#{Arity := OtherMod} ->
289-
Error = {ambiguous_call, {Mod, OtherMod, Name, Arity}},
298+
Error = {import, {ambiguous, [Mod, OtherMod]}, Name, Arity},
290299
elixir_errors:file_error(Meta, E, ?MODULE, Error);
291300

292301
#{} ->
@@ -311,11 +320,7 @@ find_import_by_name_arity(Meta, {_Name, Arity} = Tuple, Extra, E) ->
311320
{[], [Receiver]} -> {macro, Receiver};
312321
{[Receiver], []} -> {function, Receiver};
313322
{[], []} -> false;
314-
_ ->
315-
{Name, Arity} = Tuple,
316-
[First, Second | _] = FunMatch ++ MacMatch,
317-
Error = {ambiguous_call, {First, Second, Name, Arity}},
318-
elixir_errors:file_error(Meta, E, ?MODULE, Error)
323+
_ -> {ambiguous, FunMatch ++ MacMatch}
319324
end
320325
end.
321326

@@ -352,11 +357,11 @@ prune_stacktrace([], _MFA, Info, _E) ->
352357

353358
%% ERROR HANDLING
354359

355-
format_error({macro_conflict, {Receiver, Name, Arity}}) ->
360+
format_error({import, {conflict, Receiver}, Name, Arity}) ->
356361
io_lib:format("call to local macro ~ts/~B conflicts with imported ~ts.~ts/~B, "
357362
"please rename the local macro or remove the conflicting import",
358363
[Name, Arity, elixir_aliases:inspect(Receiver), Name, Arity]);
359-
format_error({ambiguous_call, {Mod1, Mod2, Name, Arity}}) ->
364+
format_error({import, {ambiguous, [Mod1, Mod2 | _]}, Name, Arity}) ->
360365
io_lib:format("function ~ts/~B imported from both ~ts and ~ts, call is ambiguous",
361366
[Name, Arity, elixir_aliases:inspect(Mod1), elixir_aliases:inspect(Mod2)]);
362367
format_error({compile_env, Name, Arity}) ->

lib/elixir/test/elixir/macro/env_test.exs

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -177,8 +177,19 @@ defmodule Macro.EnvTest do
177177
end
178178

179179
describe "expand_import/5" do
180-
test "returns :error for unknown imports" do
181-
assert :error = expand_import(env(), meta(), :flatten, 1)
180+
test "returns tagged :error for unknown imports" do
181+
assert {:error, :not_found} = expand_import(env(), meta(), :flatten, 1)
182+
end
183+
184+
test "returns tagged :error for special forms" do
185+
assert {:error, :not_found} = expand_import(env(), meta(), :case, 1)
186+
end
187+
188+
test "returns tagged :error for ambiguous" do
189+
import Date, warn: false
190+
import Time, warn: false
191+
assert {:error, {:ambiguous, mods}} = expand_import(__ENV__, meta(), :new, 3)
192+
assert Enum.sort(mods) == [Date, Time]
182193
end
183194

184195
test "returns :function tuple" do

0 commit comments

Comments
 (0)