Skip to content

Commit 1184fca

Browse files
authored
Improve error messages for dot syntax (#12003)
1 parent e7bdf1d commit 1184fca

File tree

4 files changed

+74
-28
lines changed

4 files changed

+74
-28
lines changed

lib/elixir/lib/exception.ex

+14-5
Original file line numberDiff line numberDiff line change
@@ -824,8 +824,8 @@ defmodule ArgumentError do
824824
not is_atom(module) and is_atom(function) and args == [] ->
825825
"you attempted to apply a function named #{inspect(function)} on #{inspect(module)}. " <>
826826
"If you are using Kernel.apply/3, make sure the module is an atom. " <>
827-
"If you are using the dot syntax, such as map.field or module.function(), " <>
828-
"make sure the left side of the dot is an atom or a map"
827+
"If you are using the dot syntax, such as module.function(), " <>
828+
"make sure the left-hand side of the dot is a module atom"
829829

830830
not is_atom(module) ->
831831
"you attempted to apply a function on #{inspect(module)}. " <>
@@ -1114,8 +1114,8 @@ defmodule UndefinedFunctionError do
11141114
end
11151115

11161116
defp hint(nil, _function, 0, _loaded?) do
1117-
". If you are using the dot syntax, such as map.field or module.function(), " <>
1118-
"make sure the left side of the dot is an atom or a map"
1117+
". If you are using the dot syntax, such as module.function(), " <>
1118+
"make sure the left-hand side of the dot is a module atom"
11191119
end
11201120

11211121
defp hint(module, function, arity, true) do
@@ -1635,10 +1635,19 @@ defmodule ErlangError do
16351635
%KeyError{key: key, term: term}
16361636
end
16371637

1638-
def normalize({:badkey, key, map}, _stacktrace) do
1638+
def normalize({:badkey, key, map}, _stacktrace) when is_map(map) do
16391639
%KeyError{key: key, term: map}
16401640
end
16411641

1642+
def normalize({:badkey, key, term}, _stacktrace) do
1643+
message =
1644+
"key #{inspect(key)} not found in: #{inspect(term)}. " <>
1645+
"If you are using the dot syntax, such as map.field, " <>
1646+
"make sure the left-hand side of the dot is a map"
1647+
1648+
%KeyError{key: key, term: term, message: message}
1649+
end
1650+
16421651
def normalize({:case_clause, term}, _stacktrace) do
16431652
%CaseClauseError{term: term}
16441653
end

lib/elixir/src/elixir_erl_pass.erl

+37-17
Original file line numberDiff line numberDiff line change
@@ -224,30 +224,50 @@ translate({{'.', _, [Left, Right]}, Meta, []}, _Ann, #elixir_erl{context=guard}
224224
TRight = {atom, Ann, Right},
225225
{?remote(Ann, erlang, map_get, [TRight, TLeft]), SL};
226226

227-
translate({{'.', _, [Left, Right]}, Meta, []}, _Ann, S) when is_tuple(Left), is_atom(Right), is_list(Meta) ->
227+
translate({{'.', _, [Left, Right]}, Meta, []}, _Ann, S)
228+
when is_tuple(Left) orelse Left =:= nil orelse is_boolean(Left), is_atom(Right), is_list(Meta) ->
228229
Ann = ?ann(Meta),
229230
{TLeft, SL} = translate(Left, Ann, S),
230231
TRight = {atom, Ann, Right},
231232

232233
Generated = erl_anno:set_generated(true, Ann),
233234
{Var, SV} = elixir_erl_var:build('_', SL),
234235
TVar = {var, Generated, Var},
235-
TError = {tuple, Ann, [{atom, Ann, badkey}, TRight, TVar]},
236-
237-
{{'case', Generated, TLeft, [
238-
{clause, Generated,
239-
[{map, Ann, [{map_field_exact, Ann, TRight, TVar}]}],
240-
[],
241-
[TVar]},
242-
{clause, Generated,
243-
[TVar],
244-
[[?remote(Generated, erlang, is_map, [TVar])]],
245-
[?remote(Ann, erlang, error, [TError])]},
246-
{clause, Generated,
247-
[TVar],
248-
[],
249-
[{call, Generated, {remote, Generated, TVar, TRight}, []}]}
250-
]}, SV};
236+
237+
case proplists:get_value(no_parens, Meta, false) of
238+
true ->
239+
TError = {tuple, Ann, [{atom, Ann, badkey}, TRight, TVar]},
240+
{{'case', Generated, TLeft, [
241+
{clause, Generated,
242+
[{map, Ann, [{map_field_exact, Ann, TRight, TVar}]}],
243+
[],
244+
[TVar]},
245+
{clause, Generated,
246+
[TVar],
247+
[[
248+
?remote(Generated, erlang, is_atom, [TVar]),
249+
{op, Generated, '=/=', TVar, {atom, Generated, nil}},
250+
{op, Generated, '=/=', TVar, {atom, Generated, true}},
251+
{op, Generated, '=/=', TVar, {atom, Generated, false}}
252+
]],
253+
[{call, Generated, {remote, Generated, TVar, TRight}, []}]},
254+
{clause, Generated,
255+
[TVar],
256+
[],
257+
[?remote(Ann, erlang, error, [TError])]}
258+
]}, SV};
259+
false ->
260+
{{'case', Generated, TLeft, [
261+
{clause, Generated,
262+
[{map, Ann, [{map_field_exact, Ann, TRight, TVar}]}],
263+
[],
264+
[TVar]},
265+
{clause, Generated,
266+
[TVar],
267+
[],
268+
[{call, Generated, {remote, Generated, TVar, TRight}, []}]}
269+
]}, SV}
270+
end;
251271

252272
translate({{'.', _, [Left, Right]}, Meta, Args}, _Ann, S)
253273
when (is_tuple(Left) orelse is_atom(Left)), is_atom(Right), is_list(Meta), is_list(Args) ->

lib/elixir/test/elixir/exception_test.exs

+22-5
Original file line numberDiff line numberDiff line change
@@ -478,15 +478,15 @@ defmodule ExceptionTest do
478478
end
479479

480480
test "annotates badarg on apply" do
481-
assert blame_message([], & &1.foo) ==
481+
assert blame_message([], & &1.foo()) ==
482482
"you attempted to apply a function named :foo on []. If you are using Kernel.apply/3, make sure " <>
483483
"the module is an atom. If you are using the dot syntax, such as " <>
484-
"map.field or module.function(), make sure the left side of the dot is an atom or a map"
484+
"module.function(), make sure the left-hand side of the dot is a module atom"
485485

486486
assert blame_message([], &apply(&1, :foo, [])) ==
487487
"you attempted to apply a function named :foo on []. If you are using Kernel.apply/3, make sure " <>
488488
"the module is an atom. If you are using the dot syntax, such as " <>
489-
"map.field or module.function(), make sure the left side of the dot is an atom or a map"
489+
"module.function(), make sure the left-hand side of the dot is a module atom"
490490

491491
assert blame_message([], &apply(Kernel, &1, [1, 2])) ==
492492
"you attempted to apply a function named [] on module Kernel. However [] is not a valid function name. " <>
@@ -588,10 +588,27 @@ defmodule ExceptionTest do
588588
"function :erlang.hash/2 is undefined or private, use erlang:phash2/2 instead"
589589
end
590590

591-
test "annotates undefined function clause error with nil hints" do
591+
test "annotates undefined key error with nil hints" do
592592
assert blame_message(nil, & &1.foo) ==
593+
"key :foo not found in: nil. If you are using the dot syntax, " <>
594+
"such as map.field, make sure the left-hand side of the dot is a map"
595+
596+
# we use `Code.eval_string/1` to escape the formatter and warnings
597+
assert blame_message("nil.foo", &Code.eval_string/1) ==
598+
"key :foo not found in: nil. If you are using the dot syntax, " <>
599+
"such as map.field, make sure the left-hand side of the dot is a map"
600+
end
601+
602+
test "annotates undefined function clause error with nil hints" do
603+
assert blame_message(nil, & &1.foo()) ==
604+
"function nil.foo/0 is undefined. If you are using the dot syntax, " <>
605+
"such as module.function(), make sure the left-hand side of " <>
606+
"the dot is a module atom"
607+
608+
assert blame_message("nil.foo()", &Code.eval_string/1) ==
593609
"function nil.foo/0 is undefined. If you are using the dot syntax, " <>
594-
"such as map.field or module.function(), make sure the left side of the dot is an atom or a map"
610+
"such as module.function(), make sure the left-hand side of " <>
611+
"the dot is a module atom"
595612
end
596613

597614
test "annotates key error with suggestions if keys are atoms" do

lib/elixir/test/elixir/kernel/errors_test.exs

+1-1
Original file line numberDiff line numberDiff line change
@@ -862,7 +862,7 @@ defmodule Kernel.ErrorsTest do
862862
"defmodule MisplacedOperator, do: (def bar(1 | 2), do: :ok)"
863863
end
864864

865-
defp bad_remote_call(x), do: x.foo
865+
defp bad_remote_call(x), do: x.foo()
866866

867867
defmacro sample(0), do: 0
868868

0 commit comments

Comments
 (0)