Skip to content

Commit

Permalink
Skip Erlang functions that have empty docs (#1384)
Browse files Browse the repository at this point in the history
  • Loading branch information
wojtekmach authored Jul 28, 2021
1 parent d09aac0 commit 38c672f
Show file tree
Hide file tree
Showing 5 changed files with 103 additions and 61 deletions.
29 changes: 16 additions & 13 deletions lib/ex_doc/language.ex
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ defmodule ExDoc.Language do
@callback module_data(module(), tuple(), ExDoc.Config.t()) :: module_data() | :skip

@doc """
Returns a map with function information.
Returns a map with function information or an atom `:skip`.
The map has the following keys:
Expand All @@ -67,6 +67,7 @@ defmodule ExDoc.Language do
line: non_neg_integer() | nil,
specs: [spec_ast()]
}
| :skip

@doc """
Returns a map with callback information.
Expand All @@ -83,12 +84,13 @@ defmodule ExDoc.Language do
* `:specs` - a list of specs that will be later formatted by `c:typespec/2`
"""
@callback callback_data(entry :: tuple(), module_data()) :: %{
actual_def: {atom(), arity()},
line: non_neg_integer() | nil,
signature: [binary()],
specs: [spec_ast()]
}
@callback callback_data(entry :: tuple(), module_data()) ::
%{
actual_def: {atom(), arity()},
line: non_neg_integer() | nil,
signature: [binary()],
specs: [spec_ast()]
}

@doc """
Returns a map with type information.
Expand All @@ -103,12 +105,13 @@ defmodule ExDoc.Language do
* `:spec` - a spec that will be later formatted by `c:typespec/2`
"""
@callback type_data(entry :: tuple(), spec :: term()) :: %{
type: :type | :opaque,
line: non_neg_integer(),
signature: [binary()],
spec: spec_ast()
}
@callback type_data(entry :: tuple(), spec :: term()) ::
%{
type: :type | :opaque,
line: non_neg_integer(),
signature: [binary()],
spec: spec_ast()
}

@doc """
Autolinks docs.
Expand Down
37 changes: 36 additions & 1 deletion lib/ex_doc/language/elixir.ex
Original file line number Diff line number Diff line change
Expand Up @@ -42,8 +42,16 @@ defmodule ExDoc.Language.Elixir do

@impl true
def function_data(entry, module_data) do
{{kind, name, arity}, _anno, _signature, _doc_content, metadata} = entry
{{kind, name, arity}, _anno, _signature, doc_content, metadata} = entry

if doc?(entry, module_data.type) do
function_data(kind, name, arity, doc_content, metadata, module_data)
else
:skip
end
end

def function_data(kind, name, arity, _doc_content, metadata, module_data) do
extra_annotations =
case {kind, name, arity} do
{:macro, _, _} -> ["macro"]
Expand All @@ -66,6 +74,33 @@ defmodule ExDoc.Language.Elixir do
}
end

# We are only interested in functions and macros for now
defp doc?({{kind, _, _}, _, _, _, _}, _) when kind not in [:function, :macro] do
false
end

# Skip impl_for and impl_for! for protocols
defp doc?({{_, name, _}, _, _, _, _}, :protocol) when name in [:impl_for, :impl_for!] do
false
end

# If content is a map, then it is ok.
defp doc?({_, _, _, %{}, _}, _) do
true
end

# We keep this clause with backwards compatibility with Elixir,
# from v1.12+, functions not starting with _ always default to %{}.
# TODO: Remove me once we require Elixir v1.12.
defp doc?({{_, name, _}, _, _, :none, _}, _type) do
hd(Atom.to_charlist(name)) != ?_
end

# Everything else is hidden.
defp doc?({_, _, _, _, _}, _) do
false
end

@impl true
def callback_data(entry, module_data) do
{{kind, name, arity}, anno, _signature, _doc, _metadata} = entry
Expand Down
22 changes: 18 additions & 4 deletions lib/ex_doc/language/erlang.ex
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,17 @@ defmodule ExDoc.Language.Erlang do
alias ExDoc.{Autolink, Refs}

@impl true
def module_data(_module, {:docs_v1, _, _, _, doc, _, _}, _config) when not is_map(doc) do
:skip
def module_data(module, docs_chunk, _config) do
{:docs_v1, _, _, _, doc, _, _} = docs_chunk

if is_map(doc) do
module_data(module, docs_chunk)
else
:skip
end
end

def module_data(module, docs_chunk, _config) do
def module_data(module, docs_chunk) do
":" <> id = inspect(module)
abst_code = get_abstract_code(module)
line = find_module_line(module, abst_code)
Expand All @@ -35,8 +41,16 @@ defmodule ExDoc.Language.Erlang do

@impl true
def function_data(entry, module_data) do
{{_kind, name, arity}, _anno, _signature, _doc_content, _metadata} = entry
{{kind, name, arity}, _anno, _signature, doc_content, _metadata} = entry

if kind == :function and is_map(doc_content) do
function_data(name, arity, doc_content, module_data)
else
:skip
end
end

defp function_data(name, arity, _doc_content, module_data) do
specs =
case Map.fetch(module_data.private.specs, {name, arity}) do
{:ok, specs} ->
Expand Down
61 changes: 18 additions & 43 deletions lib/ex_doc/retriever.ex
Original file line number Diff line number Diff line change
Expand Up @@ -166,49 +166,24 @@ defmodule ExDoc.Retriever do

## Function helpers

defp get_docs(%{type: type, docs: docs} = module_data, source, groups_for_functions) do
{:docs_v1, _, _, _, _, _, doc_elements} = docs
defp get_docs(module_data, source, groups_for_functions) do
{:docs_v1, _, _, _, _, _, doc_elements} = module_data.docs

function_doc_elements =
for doc_element <- doc_elements, doc?(doc_element, type) do
get_function(doc_element, source, module_data, groups_for_functions)
end

filter_defaults(function_doc_elements)
end

# TODO: Elixir specific
# We are only interested in functions and macros for now
defp doc?({{kind, _, _}, _, _, _, _}, _) when kind not in [:function, :macro] do
false
end

# TODO: Elixir specific
# Skip impl_for and impl_for! for protocols
defp doc?({{_, name, _}, _, _, _, _}, :protocol) when name in [:impl_for, :impl_for!] do
false
end
nodes =
Enum.flat_map(doc_elements, fn doc_element ->
case module_data.language.function_data(doc_element, module_data) do
:skip ->
[]

# If content is a map, then it is ok.
defp doc?({_, _, _, %{}, _}, _) do
true
end

# We keep this clause with backwards compatibility with Elixir,
# from v1.12+, functions not starting with _ always default to %{}.
# TODO: Remove me once we require Elixir v1.12.
defp doc?({{_, name, _}, _, _, :none, _}, _type) do
hd(Atom.to_charlist(name)) != ?_
end
function_data ->
[get_function(doc_element, function_data, source, module_data, groups_for_functions)]
end
end)

# Everything else is hidden.
defp doc?({_, _, _, _, _}, _) do
false
filter_defaults(nodes)
end

defp get_function(doc_element, source, module_data, groups_for_functions) do
function_data = module_data.language.function_data(doc_element, module_data)

defp get_function(doc_element, function_data, source, module_data, groups_for_functions) do
{:docs_v1, _, _, content_type, _, _, _} = module_data.docs
{{type, name, arity}, anno, signature, doc_content, metadata} = doc_element
doc_line = anno_line(anno)
Expand Down Expand Up @@ -249,14 +224,14 @@ defmodule ExDoc.Retriever do
for default <- (arity - defaults)..(arity - 1), do: {name, default}
end

defp filter_defaults(docs) do
Enum.map(docs, &filter_defaults(&1, docs))
defp filter_defaults(nodes) do
Enum.map(nodes, &filter_defaults(&1, nodes))
end

defp filter_defaults(doc, docs) do
update_in(doc.defaults, fn defaults ->
defp filter_defaults(node, nodes) do
update_in(node.defaults, fn defaults ->
Enum.reject(defaults, fn {name, arity} ->
Enum.any?(docs, &match?(%{name: ^name, arity: ^arity}, &1))
Enum.any?(nodes, &match?(%{name: ^name, arity: ^arity}, &1))
end)
end)
end
Expand Down
15 changes: 15 additions & 0 deletions test/ex_doc/retriever/erlang_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,21 @@ defmodule ExDoc.Retriever.ErlangTest do
[] = Retriever.docs_from_modules([:mod], %ExDoc.Config{})
end

@tag :otp23
@tag :otp24
test "function with no docs is skipped", c do
erlc(c, :mod, ~S"""
%% @doc Docs.
-module(mod).
-export([f/0]).
f() -> ok.
""")

[mod] = Retriever.docs_from_modules([:mod], %ExDoc.Config{})
assert mod.docs == []
end

@tag :otp24
test "callbacks", c do
erlc(c, :mod, ~S"""
Expand Down

0 comments on commit 38c672f

Please sign in to comment.