diff --git a/lib/ex_doc/language/erlang.ex b/lib/ex_doc/language/erlang.ex
index 8a6bffcb2..c21d2b8a5 100644
--- a/lib/ex_doc/language/erlang.ex
+++ b/lib/ex_doc/language/erlang.ex
@@ -69,6 +69,36 @@ defmodule ExDoc.Language.Erlang do
end
end
+ defp equiv_data(module, file, line, metadata, prefix \\ "") do
+ case metadata[:equiv] do
+ nil ->
+ nil
+
+ equiv when is_binary(equiv) ->
+ ## We try to parse the equiv in order to link to the target
+ with {:ok, toks, _} <- :erl_scan.string(:unicode.characters_to_list(equiv <> ".")),
+ {:ok, [{:call, _, {:atom, _, func}, args}]} <- :erl_parse.parse_exprs(toks) do
+ "Equivalent to [`#{equiv}`](`#{prefix}#{func}/#{length(args)}`)."
+ else
+ {:ok, [{:op, _, :/, {:atom, _, _}, {:integer, _, _}}]} ->
+ "Equivalent to `#{prefix}#{equiv}`."
+
+ _ ->
+ "Equivalent to `#{equiv}`."
+ end
+ |> ExDoc.DocAST.parse!("text/markdown")
+
+ equiv ->
+ ExDoc.Utils.warn("invalid equiv #{inspect(equiv)}",
+ file: file,
+ line: line,
+ module: module
+ )
+
+ nil
+ end
+ end
+
defp function_data(name, arity, _doc_content, module_data, metadata) do
specs =
case Map.fetch(module_data.private.specs, {name, arity}) do
@@ -88,26 +118,7 @@ defmodule ExDoc.Language.Erlang do
{file, line} = Source.get_function_location(module_data, {name, arity})
%{
- doc_fallback: fn ->
- case metadata[:equiv] do
- nil ->
- nil
-
- equiv when is_binary(equiv) ->
- ## We try to parse the equiv in order to link to the target
- with {:ok, toks, _} <- :erl_scan.string(:unicode.characters_to_list(equiv <> ".")),
- {:ok, [{:call, _, {:atom, _, func}, args}]} <- :erl_parse.parse_exprs(toks) do
- "Equivalent to [`#{equiv}`](`#{func}/#{length(args)}`)"
- else
- _ -> "Equivalent to `#{equiv}`"
- end
- |> ExDoc.DocAST.parse!("text/markdown")
-
- equiv ->
- IO.warn("invalid equiv: #{inspect(equiv)}", [])
- nil
- end
- end,
+ doc_fallback: fn -> equiv_data(module_data.module, file, line, metadata) end,
extra_annotations: [],
source_line: line,
source_file: file,
@@ -117,7 +128,7 @@ defmodule ExDoc.Language.Erlang do
@impl true
def callback_data(entry, module_data) do
- {{_kind, name, arity}, anno, signature, _doc, _metadata} = entry
+ {{_kind, name, arity}, anno, signature, _doc, metadata} = entry
extra_annotations =
if {name, arity} in module_data.private.optional_callbacks, do: ["optional"], else: []
@@ -132,6 +143,15 @@ defmodule ExDoc.Language.Erlang do
end
%{
+ doc_fallback: fn ->
+ equiv_data(
+ module_data.module,
+ Source.anno_file(anno),
+ Source.anno_line(anno),
+ metadata,
+ "c:"
+ )
+ end,
source_line: Source.anno_line(anno),
source_file: Source.anno_file(anno),
signature: signature,
@@ -142,11 +162,14 @@ defmodule ExDoc.Language.Erlang do
@impl true
def type_data(entry, module_data) do
- {{kind, name, arity}, anno, signature, _doc, _metadata} = entry
+ {{kind, name, arity}, anno, signature, _doc, metadata} = entry
case Source.get_type_from_module_data(module_data, name, arity) do
%{} = map ->
%{
+ doc_fallback: fn ->
+ equiv_data(module_data.module, map.source_file, map.source_line, metadata, "t:")
+ end,
type: map.type,
source_line: map.source_line,
source_file: map.source_file,
@@ -157,6 +180,9 @@ defmodule ExDoc.Language.Erlang do
nil ->
%{
+ doc_fallback: fn ->
+ equiv_data(module_data.module, nil, Source.anno_line(anno), metadata, "t:")
+ end,
type: kind,
source_line: Source.anno_line(anno),
spec: nil,
diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex
index 22f233fd7..aaa30cfbf 100644
--- a/lib/ex_doc/retriever.ex
+++ b/lib/ex_doc/retriever.ex
@@ -341,7 +341,9 @@ defmodule ExDoc.Retriever do
annotations_for_docs.(metadata) ++
callback_data.extra_annotations ++ annotations_from_metadata(metadata, module_metadata)
- doc_ast = doc_ast(content_type, source_doc, file: doc_file, line: doc_line + 1)
+ doc_ast =
+ doc_ast(content_type, source_doc, file: doc_file, line: doc_line + 1) ||
+ doc_fallback(callback_data)
group =
GroupMatcher.match_function(
@@ -401,7 +403,9 @@ defmodule ExDoc.Retriever do
annotations_from_metadata(metadata, module_metadata) ++
type_data.extra_annotations
- doc_ast = doc_ast(content_type, source_doc, file: doc_file, line: doc_line + 1)
+ doc_ast =
+ doc_ast(content_type, source_doc, file: doc_file, line: doc_line + 1) ||
+ doc_fallback(type_data)
group =
GroupMatcher.match_function(
@@ -429,6 +433,10 @@ defmodule ExDoc.Retriever do
## General helpers
+ defp doc_fallback(data) do
+ data[:doc_fallback] && data.doc_fallback.()
+ end
+
defp nil_or_name(name, arity) do
if name == nil do
"nil/#{arity}"
diff --git a/lib/mix/tasks/docs.ex b/lib/mix/tasks/docs.ex
index 1b1fc1662..c7319c11b 100644
--- a/lib/mix/tasks/docs.ex
+++ b/lib/mix/tasks/docs.ex
@@ -245,7 +245,9 @@ defmodule Mix.Tasks.Docs do
Functions and callbacks inside a module can also be organized in groups.
This is done via the `:groups_for_docs` configuration which is a
keyword list of group titles and filtering functions that receive the
- documentation metadata of functions as argument.
+ documentation metadata of functions as argument. The metadata received will also
+ contain `:module`, `:name`, `:arity` and `:kind` to help identify which entity is
+ currently being processed.
For example, imagine that you have an API client library with a large surface
area for all the API endpoints you need to support. It would be helpful to
diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs
index f1061837c..083bf6c43 100644
--- a/test/ex_doc/retriever/erlang_test.exs
+++ b/test/ex_doc/retriever/erlang_test.exs
@@ -33,14 +33,17 @@ defmodule ExDoc.Retriever.ErlangTest do
erlc(c, :mod, ~S"""
-module(mod).
-moduledoc("mod docs.").
- -export([function1/0, function2/0]).
+ -export([function1/0, function2/1, equiv_function2/0]).
-doc("function1/0 docs.").
-spec function1() -> atom().
function1() -> ok.
- -doc("function2/0 docs.").
- function2() -> ok.
+ -doc("function2/1 docs.").
+ function2(Opts) -> Opts.
+
+ -doc #{ equiv => function2([{test, args}]) }.
+ equiv_function2() -> function2([{test, args}]).
""")
{[mod], []} = Retriever.docs_from_modules([:mod], %ExDoc.Config{})
@@ -49,7 +52,7 @@ defmodule ExDoc.Retriever.ErlangTest do
deprecated: nil,
moduledoc_line: 2,
moduledoc_file: moduledoc_file,
- docs: [function1, function2],
+ docs: [equiv_function2, function1, function2],
docs_groups: [:Types, :Callbacks, :Functions],
group: nil,
id: "mod",
@@ -93,11 +96,18 @@ defmodule ExDoc.Retriever.ErlangTest do
"function1() -> atom()."
%ExDoc.FunctionNode{
- id: "function2/0"
+ id: "function2/1"
} = function2
- assert DocAST.to_string(function2.doc) =~ "function2/0 docs."
+ assert DocAST.to_string(function2.doc) =~ "function2/1 docs."
assert function2.specs == []
+
+ %ExDoc.FunctionNode{
+ id: "equiv_function2/0"
+ } = equiv_function2
+
+ assert DocAST.to_string(equiv_function2.doc) =~
+ ~r'Equivalent to ]+>function2\(\[\{test, args\}\]\).*\.'
end
test "module included files", c do
@@ -222,6 +232,9 @@ defmodule ExDoc.Retriever.ErlangTest do
-doc("callback1/0 docs.").
-callback callback1() -> atom().
+ -doc #{ equiv => callback1() }.
+ -callback equiv_callback1() -> atom().
+
-doc("optional_callback1/0 docs.").
-callback optional_callback1() -> atom().
@@ -230,7 +243,7 @@ defmodule ExDoc.Retriever.ErlangTest do
config = %ExDoc.Config{source_url_pattern: "%{path}:%{line}"}
{[mod], []} = Retriever.docs_from_modules([:mod], config)
- [callback1, optional_callback1] = mod.docs
+ [callback1, equiv_callback1, optional_callback1] = mod.docs
assert callback1.id == "c:callback1/0"
assert callback1.type == :callback
@@ -242,6 +255,16 @@ defmodule ExDoc.Retriever.ErlangTest do
assert Erlang.autolink_spec(hd(callback1.specs), current_kfa: {:callback, :callback1, 0}) ==
"callback1() -> atom()."
+ assert equiv_callback1.id == "c:equiv_callback1/0"
+ assert equiv_callback1.type == :callback
+ assert equiv_callback1.annotations == []
+ assert equiv_callback1.group == :Callbacks
+
+ assert DocAST.to_string(equiv_callback1.doc) =~
+ ~r'Equivalent to ]+>callback1().*\.'
+
+ assert Path.basename(equiv_callback1.source_url) == "mod.erl:7"
+
assert optional_callback1.id == "c:optional_callback1/0"
assert optional_callback1.type == :callback
assert optional_callback1.group == :Callbacks
@@ -251,18 +274,21 @@ defmodule ExDoc.Retriever.ErlangTest do
test "types", c do
erlc(c, :mod, ~S"""
-module(mod).
- -export_type([type1/0, opaque1/0]).
+ -export_type([type1/0, equiv_type1/0, opaque1/0]).
-doc("type1/0 docs.").
-type type1() :: atom().
+ -doc #{ equiv => type1/1 }.
+ -type equiv_type1() :: atom().
+
-doc("opaque1/0 docs.").
-opaque opaque1() :: atom().
""")
config = %ExDoc.Config{source_url_pattern: "%{path}:%{line}"}
{[mod], []} = Retriever.docs_from_modules([:mod], config)
- [opaque1, type1] = mod.typespecs
+ [equiv_type1, opaque1, type1] = mod.typespecs
assert opaque1.id == "t:opaque1/0"
assert opaque1.type == :opaque
@@ -281,6 +307,12 @@ defmodule ExDoc.Retriever.ErlangTest do
assert type1.spec |> Erlang.autolink_spec(current_kfa: {:type, :type1, 0}) ==
"type1() :: atom()."
+
+ assert equiv_type1.id == "t:equiv_type1/0"
+ assert equiv_type1.type == :type
+ assert equiv_type1.group == :Types
+ assert equiv_type1.signature == "equiv_type1()"
+ assert equiv_type1.doc |> DocAST.to_string() =~ ~r'Equivalent to .*t:type1/1.*\.'
end
test "records", c do