Skip to content

Commit dadb412

Browse files
fertapricjosevalim
authored andcommitted
Use typespec info in IEx.Helpers.b/1 (#8514)
The previous approach was using the docs chunk as the source of truth. Because of that, Protocols or Erlang/OTP modules were not showing callback information.
1 parent 93ceb95 commit dadb412

File tree

2 files changed

+125
-54
lines changed

2 files changed

+125
-54
lines changed

lib/iex/lib/iex/introspection.ex

Lines changed: 61 additions & 53 deletions
Original file line numberDiff line numberDiff line change
@@ -287,7 +287,7 @@ defmodule IEx.Introspection do
287287
result =
288288
for {^function, arity} <- exports,
289289
(if docs do
290-
find_doc(docs, function, arity)
290+
find_doc_with_content(docs, function, arity)
291291
else
292292
get_spec(module, function, arity) != []
293293
end) do
@@ -364,7 +364,7 @@ defmodule IEx.Introspection do
364364
spec = get_spec(mod, fun, arity)
365365

366366
cond do
367-
doc_tuple = find_doc(docs, fun, arity) ->
367+
doc_tuple = find_doc_with_content(docs, fun, arity) ->
368368
print_fun(mod, doc_tuple, spec)
369369
:ok
370370

@@ -388,15 +388,17 @@ defmodule IEx.Introspection do
388388
end
389389

390390
defp has_callback?(mod, fun) do
391-
mod
392-
|> get_docs([:callback, :macrocallback])
393-
|> Enum.any?(&match?({_, ^fun, _}, elem(&1, 0)))
391+
case get_callback_docs(mod, &match?({_, ^fun, _}, elem(&1, 0))) do
392+
{:ok, [_ | _]} -> true
393+
_ -> false
394+
end
394395
end
395396

396397
defp has_callback?(mod, fun, arity) do
397-
mod
398-
|> get_docs([:callback, :macrocallback])
399-
|> Enum.any?(&match?({_, ^fun, ^arity}, elem(&1, 0)))
398+
case get_callback_docs(mod, &match?({_, ^fun, ^arity}, elem(&1, 0))) do
399+
{:ok, [_ | _]} -> true
400+
_ -> false
401+
end
400402
end
401403

402404
defp has_type?(mod, fun) do
@@ -423,16 +425,22 @@ defmodule IEx.Introspection do
423425

424426
defp extract_name_and_arity({{_, name, arity}, _, _, _, _}), do: {name, arity}
425427

428+
defp find_doc_with_content(docs, function, arity) do
429+
doc = find_doc(docs, function, arity)
430+
if doc != nil and has_content?(doc), do: doc
431+
end
432+
433+
defp has_content?({_, _, _, :hidden, _}), do: false
434+
defp has_content?({{_, name, _}, _, _, :none, _}), do: hd(Atom.to_charlist(name)) != ?_
435+
defp has_content?({_, _, _, _, _}), do: true
436+
426437
defp find_doc(nil, _fun, _arity) do
427438
nil
428439
end
429440

430441
defp find_doc(docs, fun, arity) do
431-
doc =
432-
Enum.find(docs, &match?({_, ^fun, ^arity}, elem(&1, 0))) ||
433-
find_doc_defaults(docs, fun, arity)
434-
435-
if doc != nil and has_content?(doc), do: doc
442+
Enum.find(docs, &match?({_, ^fun, ^arity}, elem(&1, 0))) ||
443+
find_doc_defaults(docs, fun, arity)
436444
end
437445

438446
defp find_doc_defaults(docs, function, min) do
@@ -445,10 +453,6 @@ defmodule IEx.Introspection do
445453
end)
446454
end
447455

448-
defp has_content?({_, _, _, :hidden, _}), do: false
449-
defp has_content?({{_, name, _}, _, _, :none, _}), do: hd(Atom.to_charlist(name)) != ?_
450-
defp has_content?({_, _, _, _, _}), do: true
451-
452456
defp print_fun(mod, {{kind, fun, arity}, _line, signature, doc, metadata}, spec) do
453457
if callback_module = doc == :none and callback_module(mod, fun, arity) do
454458
filter = &match?({_, ^fun, ^arity}, elem(&1, 0))
@@ -466,19 +470,10 @@ defmodule IEx.Introspection do
466470
defp kind_to_def(:macro), do: :defmacro
467471

468472
defp callback_module(mod, fun, arity) do
469-
predicate = &match?({{^fun, ^arity}, _}, &1)
470-
471473
mod.module_info(:attributes)
472474
|> Keyword.get_values(:behaviour)
473475
|> Stream.concat()
474-
|> Enum.find(&Enum.any?(get_callbacks(&1), predicate))
475-
end
476-
477-
defp get_callbacks(module) do
478-
case Typespec.fetch_callbacks(module) do
479-
{:ok, callbacks} -> callbacks
480-
:error -> []
481-
end
476+
|> Enum.find(&has_callback?(&1, fun, arity))
482477
end
483478

484479
defp get_spec(module, name, arity) do
@@ -504,9 +499,6 @@ defmodule IEx.Introspection do
504499
:no_beam ->
505500
no_beam(mod)
506501

507-
:no_docs ->
508-
no_docs(mod)
509-
510502
{:ok, []} ->
511503
puts_error("No callbacks for #{inspect(mod)} were found")
512504

@@ -524,7 +516,6 @@ defmodule IEx.Introspection do
524516

525517
case get_callback_docs(mod, filter) do
526518
:no_beam -> no_beam(mod)
527-
:no_docs -> no_docs(mod)
528519
{:ok, []} -> docs_not_found("#{inspect(mod)}.#{fun}")
529520
{:ok, docs} -> Enum.each(docs, &print_typespec/1)
530521
end
@@ -537,7 +528,6 @@ defmodule IEx.Introspection do
537528

538529
case get_callback_docs(mod, filter) do
539530
:no_beam -> no_beam(mod)
540-
:no_docs -> no_docs(mod)
541531
{:ok, []} -> docs_not_found("#{inspect(mod)}.#{fun}/#{arity}")
542532
{:ok, docs} -> Enum.each(docs, &print_typespec/1)
543533
end
@@ -557,26 +547,54 @@ defmodule IEx.Introspection do
557547
:error ->
558548
:no_beam
559549

560-
_ when is_nil(docs) ->
561-
:no_docs
562-
563550
{:ok, callbacks} ->
564551
docs =
565-
docs
552+
callbacks
553+
|> Enum.map(&translate_callback/1)
566554
|> Enum.filter(filter)
567-
|> Enum.map(fn
568-
{{:macrocallback, fun, arity}, _, _, doc, metadata} ->
569-
macro = {:"MACRO-#{fun}", arity + 1}
570-
{format_callback(:macrocallback, fun, macro, callbacks), doc, metadata}
571-
572-
{{kind, fun, arity}, _, _, doc, metadata} ->
573-
{format_callback(kind, fun, {fun, arity}, callbacks), doc, metadata}
555+
|> Enum.sort()
556+
|> Enum.flat_map(fn {{_, function, arity}, _specs} = callback ->
557+
case find_doc(docs, function, arity) do
558+
nil -> [{format_callback(callback), :none, %{}}]
559+
{_, _, _, :hidden, _} -> []
560+
{_, _, _, doc, metadata} -> [{format_callback(callback), doc, metadata}]
561+
end
574562
end)
575563

576564
{:ok, docs}
577565
end
578566
end
579567

568+
defp translate_callback({{name, arity}, specs}) do
569+
case Atom.to_string(name) do
570+
"MACRO-" <> macro_name ->
571+
# The typespec of a macrocallback differs from the one expressed
572+
# via @macrocallback:
573+
#
574+
# * The function name is prefixed with "MACRO-"
575+
# * The arguments contain an additional first argument: the caller
576+
# * The arity is increased by 1
577+
#
578+
specs =
579+
Enum.map(specs, fn {:type, line1, :fun, [{:type, line2, :product, [_ | args]}, spec]} ->
580+
{:type, line1, :fun, [{:type, line2, :product, args}, spec]}
581+
end)
582+
583+
{{:macrocallback, String.to_atom(macro_name), arity - 1}, specs}
584+
585+
_ ->
586+
{{:callback, name, arity}, specs}
587+
end
588+
end
589+
590+
defp format_callback({{kind, name, _arity}, specs}) do
591+
Enum.map(specs, fn spec ->
592+
Typespec.spec_to_quoted(name, spec)
593+
|> Macro.prewalk(&drop_macro_env/1)
594+
|> format_typespec(kind, 0)
595+
end)
596+
end
597+
580598
defp add_optional_callback_docs(docs, mod) do
581599
optional_callbacks =
582600
if Code.ensure_loaded?(mod) and function_exported?(mod, :behaviour_info, 1) do
@@ -596,16 +614,6 @@ defmodule IEx.Introspection do
596614
format_typespec(callbacks, :optional_callbacks, 0)
597615
end
598616

599-
defp format_callback(kind, name, key, callbacks) do
600-
{_, specs} = List.keyfind(callbacks, key, 0)
601-
602-
Enum.map(specs, fn spec ->
603-
Typespec.spec_to_quoted(name, spec)
604-
|> Macro.prewalk(&drop_macro_env/1)
605-
|> format_typespec(kind, 0)
606-
end)
607-
end
608-
609617
defp drop_macro_env({name, meta, [{:::, _, [_, {{:., _, [Macro.Env, :t]}, _, _}]} | args]}),
610618
do: {name, meta, args}
611619

lib/iex/test/iex/helpers_test.exs

Lines changed: 64 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -611,7 +611,7 @@ defmodule IEx.HelpersTest do
611611
end
612612

613613
describe "b" do
614-
test "lists all callbacks for a module" do
614+
test "lists all callbacks for an Elixir module" do
615615
assert capture_io(fn -> b(Mix) end) == "No callbacks for Mix were found\n"
616616
assert capture_io(fn -> b(NoMix) end) == "Could not load module NoMix, got: nofile\n"
617617

@@ -622,6 +622,43 @@ defmodule IEx.HelpersTest do
622622
"""
623623
end
624624

625+
test "lists all callbacks for an Erlang module" do
626+
output = capture_io(fn -> b(:gen_server) end)
627+
628+
assert output =~ "@callback handle_cast(request :: term(), state :: term()) ::"
629+
assert output =~ "@callback handle_info(info :: :timeout | term(), state :: term()) ::"
630+
assert output =~ "@callback init(args :: term()) ::"
631+
end
632+
633+
test "lists all macrocallbacks for a module" do
634+
filename = "macrocallbacks.ex"
635+
636+
content = """
637+
defmodule Macrocallbacks do
638+
@macrocallback test(:foo) :: integer
639+
end
640+
"""
641+
642+
with_file(filename, content, fn ->
643+
assert c(filename, ".") == [Macrocallbacks]
644+
645+
assert capture_io(fn -> b(Macrocallbacks) end) =~
646+
"@macrocallback test(:foo) :: integer()\n\n"
647+
end)
648+
after
649+
cleanup_modules([Macrocallbacks])
650+
end
651+
652+
test "lists all callbacks for a protocol" do
653+
assert capture_io(fn -> b(Enumerable) end) =~ """
654+
@callback count(t()) :: {:ok, non_neg_integer()} | {:error, module()}
655+
656+
@callback member?(t(), term()) :: {:ok, boolean()} | {:error, module()}
657+
658+
@callback reduce(t(), acc(), reducer()) :: result()
659+
"""
660+
end
661+
625662
test "lists callback with multiple clauses" do
626663
filename = "multiple_clauses_callback.ex"
627664

@@ -656,6 +693,9 @@ defmodule IEx.HelpersTest do
656693

657694
assert capture_io(fn -> b(Exception.message() / 1) end) ==
658695
"@callback message(t()) :: String.t()\n\n"
696+
697+
assert capture_io(fn -> b(:gen_server.handle_cast() / 2) end) =~
698+
"@callback handle_cast(request :: term(), state :: term()) ::"
659699
end
660700

661701
test "prints callback documentation metadata" do
@@ -703,6 +743,29 @@ defmodule IEx.HelpersTest do
703743
after
704744
cleanup_modules([OptionalCallbacks])
705745
end
746+
747+
test "does not print docs for @doc false callbacks" do
748+
filename = "hidden_callbacks.ex"
749+
750+
content = """
751+
defmodule HiddenCallbacks do
752+
@doc false
753+
@callback hidden_callback() :: integer
754+
755+
@doc false
756+
@macrocallback hidden_macrocallback() :: integer
757+
end
758+
"""
759+
760+
with_file(filename, content, fn ->
761+
assert c(filename, ".") == [HiddenCallbacks]
762+
763+
assert capture_io(fn -> b(HiddenCallbacks) end) =~
764+
"No callbacks for HiddenCallbacks were found\n"
765+
end)
766+
after
767+
cleanup_modules([HiddenCallbacks])
768+
end
706769
end
707770

708771
describe "t" do

0 commit comments

Comments
 (0)