From e81a31b301181a13f56afce20eca6475871e73f5 Mon Sep 17 00:00:00 2001 From: lud Date: Wed, 9 Apr 2025 08:30:15 +0200 Subject: [PATCH 1/8] Allow groups to carry descriptions --- .../epub/templates/module_template.eex | 6 +-- lib/ex_doc/formatter/html/templates.ex | 11 ++++- .../html/templates/module_template.eex | 6 +-- lib/ex_doc/group_matcher.ex | 2 +- lib/ex_doc/nodes.ex | 6 ++- lib/ex_doc/retriever.ex | 45 ++++++++++++++++++- test/ex_doc/retriever/erlang_test.exs | 6 +-- test/ex_doc/retriever_test.exs | 32 +++++++++++++ 8 files changed, 99 insertions(+), 15 deletions(-) diff --git a/lib/ex_doc/formatter/epub/templates/module_template.eex b/lib/ex_doc/formatter/epub/templates/module_template.eex index 2639baddd..282d83c5c 100644 --- a/lib/ex_doc/formatter/epub/templates/module_template.eex +++ b/lib/ex_doc/formatter/epub/templates/module_template.eex @@ -18,13 +18,13 @@ <%= if summary != [] do %>

Summary

- <%= for {name, nodes} <- summary, do: H.summary_template(name, nodes) %> + <%= for {group, nodes} <- summary, do: H.summary_template(group.title, nodes) %>
<% end %> - <%= for {name, nodes} <- summary, key = text_to_id(name) do %> + <%= for {group, nodes} <- summary, key = text_to_id(group.title) do %>
-

<%=h to_string(name) %>

+

<%=h to_string(group.title) %>

<%= for node <- nodes, do: H.detail_template(node, module) %>
diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex index 80d180548..093592a0d 100644 --- a/lib/ex_doc/formatter/html/templates.ex +++ b/lib/ex_doc/formatter/html/templates.ex @@ -134,7 +134,7 @@ defmodule ExDoc.Formatter.HTML.Templates do %{id: id, title: node.signature, anchor: URI.encode(node.id), deprecated: deprecated?} end - %{key: text_to_id(group), name: group, nodes: nodes} + %{key: text_to_id(group.title), name: group.title, nodes: nodes} end defp module_sections(%ExDoc.ModuleNode{rendered_doc: nil}), do: [sections: []] @@ -169,7 +169,14 @@ defmodule ExDoc.Formatter.HTML.Templates do def module_summary(module_node) do # TODO: Maybe it should be moved to retriever and it already returned grouped metadata - ExDoc.GroupMatcher.group_by(module_node.docs_groups, module_node.docs, & &1.group) + + group_titles = Enum.map(module_node.docs_groups, & &1.title) + groups_index = Map.new(module_node.docs_groups, &{&1.title, &1}) + docs_groups = ExDoc.GroupMatcher.group_by(group_titles, module_node.docs, & &1.group) + + Enum.map(docs_groups, fn {group_title, nodes} -> + {Map.fetch!(groups_index, group_title), nodes} + end) end defp favicon_path(%{favicon: nil}), do: nil diff --git a/lib/ex_doc/formatter/html/templates/module_template.eex b/lib/ex_doc/formatter/html/templates/module_template.eex index e14af45bf..2819ad3fd 100644 --- a/lib/ex_doc/formatter/html/templates/module_template.eex +++ b/lib/ex_doc/formatter/html/templates/module_template.eex @@ -39,17 +39,17 @@ Summary - <%= for {name, nodes} <- summary, do: summary_template(name, nodes) %> + <%= for {group, nodes} <- summary, do: summary_template(group.title, nodes) %>
<% end %> -<%= for {name, nodes} <- summary, key = text_to_id(name) do %> +<%= for {group, nodes} <- summary, key = text_to_id(group.title) do %>

- <%= name %> + <%= group.title %>

<%= for node <- nodes, do: detail_template(node, module) %> diff --git a/lib/ex_doc/group_matcher.ex b/lib/ex_doc/group_matcher.ex index 6cda47c61..1bdbbd6c1 100644 --- a/lib/ex_doc/group_matcher.ex +++ b/lib/ex_doc/group_matcher.ex @@ -15,7 +15,7 @@ defmodule ExDoc.GroupMatcher do end @doc """ - Group the following entries and while preserving the order in `groups`. + Group the following entries while preserving the order in `groups`. """ def group_by(groups, entries, by) do entries = Enum.group_by(entries, by) diff --git a/lib/ex_doc/nodes.ex b/lib/ex_doc/nodes.ex index 068e9f848..2a0db14e9 100644 --- a/lib/ex_doc/nodes.ex +++ b/lib/ex_doc/nodes.ex @@ -26,6 +26,10 @@ defmodule ExDoc.ModuleNode do metadata: nil @typep annotation :: atom() + @typep doc_group :: %{ + title: String.t() | atom(), + description: String.t() | nil + } @type t :: %__MODULE__{ id: String.t(), @@ -43,7 +47,7 @@ defmodule ExDoc.ModuleNode do moduledoc_file: String.t(), source_path: String.t() | nil, source_url: String.t() | nil, - docs_groups: [atom()], + docs_groups: [doc_group], docs: [ExDoc.DocNode.t()], typespecs: [ExDoc.DocNode.t()], type: atom(), diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 128b4a18d..4243e059f 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -141,6 +141,12 @@ defmodule ExDoc.Retriever do annotations_for_docs = config.annotations_for_docs docs = get_docs(module_data, source, group_for_doc, annotations_for_docs) + + moduledoc_groups = Map.get(metadata, :groups, []) + + {docs_groups, docs} = + get_docs_groups(moduledoc_groups ++ config.docs_groups ++ module_data.default_groups, docs) + metadata = Map.put(metadata, :kind, module_data.type) group = GroupMatcher.match_module(config.groups_for_modules, module, module_data.id, metadata) {nested_title, nested_context} = module_data.nesting_info || {nil, nil} @@ -154,7 +160,7 @@ defmodule ExDoc.Retriever do module: module, type: module_data.type, deprecated: metadata[:deprecated], - docs_groups: config.docs_groups ++ module_data.default_groups, + docs_groups: docs_groups, docs: ExDoc.Utils.natural_sort_by(docs, &"#{&1.name}/#{&1.arity}"), doc_format: format, doc: doc, @@ -198,6 +204,30 @@ defmodule ExDoc.Retriever do filter_defaults(nodes) end + defp get_docs_groups(module_groups, doc_nodes) do + module_groups = Enum.map(module_groups, &normalize_group/1) + + # Doc nodes already have normalized groups + nodes_groups = Enum.map(doc_nodes, & &1.group) + + normal_groups = module_groups ++ nodes_groups + + {docs_groups, _} = + Enum.flat_map_reduce(normal_groups, %{}, fn group, seen -> + if is_map_key(seen, group.title) do + {[], seen} + else + {[group], Map.put(seen, group.title, true)} + end + end) + + # We do not need the full group data in each doc node anymore, only the + # title. + doc_nodes = Enum.map(doc_nodes, &Map.put(&1, :group, &1.group.title)) + + {docs_groups, doc_nodes} + end + defp get_doc(doc, doc_data, module_data, source, group_for_doc, annotations_for_docs) do {:docs_v1, _, _, content_type, _, module_metadata, _} = module_data.docs {{type, name, arity}, anno, _signature, source_doc, metadata} = doc @@ -222,7 +252,7 @@ defmodule ExDoc.Retriever do (source_doc && doc_ast(content_type, source_doc, file: doc_file, line: doc_line + 1)) || doc_data.doc_fallback.() - group = group_for_doc.(metadata) || doc_data.default_group + group = normalize_group(group_for_doc.(metadata) || doc_data.default_group) %ExDoc.DocNode{ id: doc_data.id_key <> nil_or_name(name, arity), @@ -314,4 +344,15 @@ defmodule ExDoc.Retriever do defp source_link(%{url_pattern: url_pattern, relative_path: path}, line) do url_pattern.(path, line) end + + defp normalize_group(group) do + case group do + %{title: title, description: description} + when is_binary(title) and (is_binary(description) or is_nil(description)) -> + group + + title when is_binary(title) when is_atom(title) -> + %{title: title, description: nil} + end + end end diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs index 671fb329f..94f43925a 100644 --- a/test/ex_doc/retriever/erlang_test.exs +++ b/test/ex_doc/retriever/erlang_test.exs @@ -59,7 +59,7 @@ defmodule ExDoc.Retriever.ErlangTest do moduledoc_line: 2, moduledoc_file: moduledoc_file, docs: [equiv_function2, function1, function2], - docs_groups: ["Types", "Callbacks", "Functions"], + docs_groups: [%{title: "Types"}, %{title: "Callbacks"}, %{title: "Functions"}], group: nil, id: "mod", language: ExDoc.Language.Erlang, @@ -156,7 +156,7 @@ defmodule ExDoc.Retriever.ErlangTest do moduledoc_line: 6, moduledoc_file: moduledoc_file, docs: [type, callback, function], - docs_groups: ["Types", "Callbacks", "Functions"], + docs_groups: [%{title: "Types"}, %{title: "Callbacks"}, %{title: "Functions"}], group: nil, id: "mod", language: ExDoc.Language.Erlang, @@ -397,7 +397,7 @@ defmodule ExDoc.Retriever.ErlangTest do deprecated: nil, moduledoc_line: _, docs: [function1, function2], - docs_groups: ["Types", "Callbacks", "Functions"], + docs_groups: [%{title: "Types"}, %{title: "Callbacks"}, %{title: "Functions"}], group: nil, id: "mod", language: ExDoc.Language.Erlang, diff --git a/test/ex_doc/retriever_test.exs b/test/ex_doc/retriever_test.exs index 80588962a..ac07be172 100644 --- a/test/ex_doc/retriever_test.exs +++ b/test/ex_doc/retriever_test.exs @@ -108,6 +108,38 @@ defmodule ExDoc.RetrieverTest do assert %{id: "baz/0", group: "c"} = baz end + test "function groups description use moduledoc :groups metadata", c do + elixirc(c, ~S""" + defmodule A do + @moduledoc groups: [ + "c", + %{title: "b", description: "text for b"} + ] + + @doc group: "a" + @callback foo() :: :ok + + @doc group: "b" + def bar(), do: :ok + + @doc group: "c" + def baz(), do: :ok + end + """) + + config = %ExDoc.Config{} + {[mod], []} = Retriever.docs_from_modules([A], config) + + assert [ + %{description: nil, title: "c"}, + %{description: "text for b", title: "b"}, + %{description: nil, title: "Types"}, + %{description: nil, title: "Callbacks"}, + %{description: nil, title: "Functions"}, + %{description: nil, title: "a"} + ] = mod.docs_groups + end + test "function annotations", c do elixirc(c, ~S""" defmodule A do From 80679ae1fc288013241c21db1324f6b13ed0b80f Mon Sep 17 00:00:00 2001 From: lud Date: Wed, 9 Apr 2025 09:10:17 +0200 Subject: [PATCH 2/8] Accept groups descriptions from callback --- lib/ex_doc/retriever.ex | 27 +++++++++++++--- test/ex_doc/retriever_test.exs | 56 ++++++++++++++++++++++++++++++++++ 2 files changed, 78 insertions(+), 5 deletions(-) diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 4243e059f..10afb554d 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -209,16 +209,29 @@ defmodule ExDoc.Retriever do # Doc nodes already have normalized groups nodes_groups = Enum.map(doc_nodes, & &1.group) + nodes_groups_descriptions = Map.new(nodes_groups, &{&1.title, &1.description}) normal_groups = module_groups ++ nodes_groups {docs_groups, _} = - Enum.flat_map_reduce(normal_groups, %{}, fn group, seen -> - if is_map_key(seen, group.title) do + Enum.flat_map_reduce(normal_groups, %{}, fn + group, seen when is_map_key(seen, group.title) -> {[], seen} - else - {[group], Map.put(seen, group.title, true)} - end + + group, seen -> + seen = Map.put(seen, group.title, group.description) + + group = + case group do + %{description: nil} -> + description = Map.get(nodes_groups_descriptions, group.title, nil) + Map.put(group, :description, description) + + _ -> + group + end + + {[group], seen} end) # We do not need the full group data in each doc node anymore, only the @@ -351,6 +364,10 @@ defmodule ExDoc.Retriever do when is_binary(title) and (is_binary(description) or is_nil(description)) -> group + kw when is_list(kw) -> + true = Keyword.keyword?(kw) + %{title: Keyword.fetch!(kw, :title), description: kw[:description]} + title when is_binary(title) when is_atom(title) -> %{title: title, description: nil} end diff --git a/test/ex_doc/retriever_test.exs b/test/ex_doc/retriever_test.exs index ac07be172..9c8eca5b6 100644 --- a/test/ex_doc/retriever_test.exs +++ b/test/ex_doc/retriever_test.exs @@ -108,6 +108,62 @@ defmodule ExDoc.RetrieverTest do assert %{id: "baz/0", group: "c"} = baz end + test "default_group_for_doc can return group description from @moduledoc", c do + elixirc(c, ~S""" + defmodule A do + + @moduledoc groups: [ + "c", + %{title: "b", description: "predefined b"} + ] + + @doc test_group: "a" + @callback foo() :: :ok + + @doc test_group: "b" + def bar(), do: :ok + + @doc test_group: "c" + def baz(), do: :ok + end + """) + + config = %ExDoc.Config{ + group_for_doc: fn meta -> + case meta[:test_group] do + "a" -> [title: "a", description: "for a"] + "b" -> [title: "b", description: "ignored description"] + "c" -> [title: "c", description: "for c"] + end + end + } + + {[mod], []} = Retriever.docs_from_modules([A], config) + + assert [c, b, types, callbacks, functions, a] = mod.docs_groups + + # Description returned by the function should override nil + assert %{title: "c", description: "for c"} = c + + # Description returned by the function should not override a + # description from @moduledoc + assert %{title: "b", description: "predefined b"} = b + + assert %{title: "Types", description: nil} = types + assert %{title: "Callbacks", description: nil} = callbacks + assert %{title: "Functions", description: nil} = functions + + # Description returned by th function should define a description + # for leftover groups + assert %{title: "a", description: "for a"} = a + + [bar, baz, foo] = mod.docs + + assert %{id: "c:foo/0", group: "a"} = foo + assert %{id: "bar/0", group: "b"} = bar + assert %{id: "baz/0", group: "c"} = baz + end + test "function groups description use moduledoc :groups metadata", c do elixirc(c, ~S""" defmodule A do From 99cf031641837e372b9555589108216c09646f1d Mon Sep 17 00:00:00 2001 From: lud Date: Wed, 9 Apr 2025 10:17:33 +0200 Subject: [PATCH 3/8] Render groups descriptions --- .../epub/templates/module_template.eex | 5 +++ lib/ex_doc/formatter/html.ex | 8 ++++- lib/ex_doc/formatter/html/templates.ex | 4 +++ .../html/templates/module_template.eex | 5 +++ lib/ex_doc/nodes.ex | 14 +++++--- lib/ex_doc/retriever.ex | 11 ++++++ test/ex_doc/formatter/epub/templates_test.exs | 36 +++++++++++++++++++ test/ex_doc/formatter/html/templates_test.exs | 36 +++++++++++++++++++ 8 files changed, 113 insertions(+), 6 deletions(-) diff --git a/lib/ex_doc/formatter/epub/templates/module_template.eex b/lib/ex_doc/formatter/epub/templates/module_template.eex index 282d83c5c..a6c9e1c38 100644 --- a/lib/ex_doc/formatter/epub/templates/module_template.eex +++ b/lib/ex_doc/formatter/epub/templates/module_template.eex @@ -25,6 +25,11 @@ <%= for {group, nodes} <- summary, key = text_to_id(group.title) do %>

<%=h to_string(group.title) %>

+ <%= if doc = group.rendered_doc do %> +
+ <%= H.link_group_headings(doc, key) %> +
+ <% end %>
<%= for node <- nodes, do: H.detail_template(node, module) %>
diff --git a/lib/ex_doc/formatter/html.ex b/lib/ex_doc/formatter/html.ex index bdc3420e8..30db0e0d2 100644 --- a/lib/ex_doc/formatter/html.ex +++ b/lib/ex_doc/formatter/html.ex @@ -111,9 +111,15 @@ defmodule ExDoc.Formatter.HTML do render_doc(child_node, language, autolink_opts, opts) end + docs_groups = + for group <- node.docs_groups do + render_doc(group, language, autolink_opts, opts) + end + %{ render_doc(node, language, [{:id, node.id} | autolink_opts], opts) - | docs: docs + | docs: docs, + docs_groups: docs_groups } end, timeout: :infinity diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex index 093592a0d..35f18e94b 100644 --- a/lib/ex_doc/formatter/html/templates.ex +++ b/lib/ex_doc/formatter/html/templates.ex @@ -288,6 +288,10 @@ defmodule ExDoc.Formatter.HTML.Templates do link_headings(content, prefix <> "-") end + def link_group_headings(content, key) do + link_headings(content, "group-#{key}-") + end + templates = [ detail_template: [:node, :module], footer_template: [:config, :node], diff --git a/lib/ex_doc/formatter/html/templates/module_template.eex b/lib/ex_doc/formatter/html/templates/module_template.eex index 2819ad3fd..d785fd914 100644 --- a/lib/ex_doc/formatter/html/templates/module_template.eex +++ b/lib/ex_doc/formatter/html/templates/module_template.eex @@ -51,6 +51,11 @@ <%= group.title %> + <%= if doc = group.rendered_doc do %> +
+ <%= link_group_headings(doc, key) %> +
+ <% end %>
<%= for node <- nodes, do: detail_template(node, module) %>
diff --git a/lib/ex_doc/nodes.ex b/lib/ex_doc/nodes.ex index 2a0db14e9..12732163b 100644 --- a/lib/ex_doc/nodes.ex +++ b/lib/ex_doc/nodes.ex @@ -26,10 +26,14 @@ defmodule ExDoc.ModuleNode do metadata: nil @typep annotation :: atom() - @typep doc_group :: %{ - title: String.t() | atom(), - description: String.t() | nil - } + + # TODO: Maybe this is worth its own module + @type doc_group :: %{ + title: String.t() | atom(), + description: String.t() | nil, + doc: ExDoc.DocAST.t() | nil, + rendered_doc: String.t() | nil + } @type t :: %__MODULE__{ id: String.t(), @@ -93,7 +97,7 @@ defmodule ExDoc.DocNode do signature: String.t(), specs: [ExDoc.Language.spec_ast()], annotations: [annotation()], - group: atom() | nil, + group: String.t() | ExDoc.ModuleNode.doc_group() | nil, doc_file: String.t(), doc_line: non_neg_integer(), source_url: String.t() | nil diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 10afb554d..cdb550ab5 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -234,6 +234,17 @@ defmodule ExDoc.Retriever do {[group], seen} end) + docs_groups = + Enum.map(docs_groups, fn group -> + doc_ast = + case group.description do + nil -> nil + text -> doc_ast("text/markdown", %{"en" => text}, []) + end + + Map.merge(group, %{doc: doc_ast, rendered_doc: nil}) + end) + # We do not need the full group data in each doc node anymore, only the # title. doc_nodes = Enum.map(doc_nodes, &Map.put(&1, :group, &1.group.title)) diff --git a/test/ex_doc/formatter/epub/templates_test.exs b/test/ex_doc/formatter/epub/templates_test.exs index 724ea3400..ff93d13e5 100644 --- a/test/ex_doc/formatter/epub/templates_test.exs +++ b/test/ex_doc/formatter/epub/templates_test.exs @@ -145,6 +145,42 @@ defmodule ExDoc.Formatter.EPUB.TemplatesTest do assert content =~ ~r{id="functions".*id="example_1/0"}ms end + test "outputs groups descriptions" do + content = + get_module_page([CompiledWithDocs], + group_for_doc: fn metadata -> + if metadata[:purpose] == :example do + [ + title: "Example functions", + description: """ + ### A section heading example + + A content example. + + See `example/1` or `example/2`. + A link to `flatten/1`. + """ + ] + else + "Functions" + end + end + ) + + doc = LazyHTML.from_document(content) + + assert Enum.count(doc["div.group-description"]) == 1 + assert Enum.count(doc["#group-description-example-functions"]) == 1 + assert Enum.count(doc["#group-description-example-functions h3"]) == 1 + assert Enum.count(doc["#group-example-functions-a-section-heading-example"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#example/1']"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#example/2']"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#flatten/1']"]) == 1 + + assert content =~ ~s[A section heading example] + assert content =~ "

A content example.

" + end + test "outputs summaries" do content = get_module_page([CompiledWithDocs]) diff --git a/test/ex_doc/formatter/html/templates_test.exs b/test/ex_doc/formatter/html/templates_test.exs index f13e21260..d0b7c404a 100644 --- a/test/ex_doc/formatter/html/templates_test.exs +++ b/test/ex_doc/formatter/html/templates_test.exs @@ -469,6 +469,42 @@ defmodule ExDoc.Formatter.HTML.TemplatesTest do assert Enum.count(doc["#functions [id='example/2']"]) == 0 end + test "outputs groups descriptions", context do + content = + get_module_page([CompiledWithDocs], context, + group_for_doc: fn metadata -> + if metadata[:purpose] == :example do + [ + title: "Example functions", + description: """ + ### A section heading example + + A content example. + + See `example/1` or `example/2`. + A link to `flatten/1`. + """ + ] + else + "Functions" + end + end + ) + + doc = LazyHTML.from_document(content) + + assert Enum.count(doc["div.group-description"]) == 1 + assert Enum.count(doc["#group-description-example-functions"]) == 1 + assert Enum.count(doc["#group-description-example-functions h3"]) == 1 + assert Enum.count(doc["#group-example-functions-a-section-heading-example"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#example/1']"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#example/2']"]) == 1 + assert Enum.count(doc["#example-functions .group-description a[href='#flatten/1']"]) == 1 + + assert content =~ ~s[A section heading example] + assert content =~ "

A content example.

" + end + test "outputs deprecation information", context do content = get_module_page([CompiledWithDocs], context) From 981f0b0708731b97a33cae2dd08a3e0b285a4748 Mon Sep 17 00:00:00 2001 From: lud Date: Wed, 9 Apr 2025 10:52:13 +0200 Subject: [PATCH 4/8] refactor --- lib/ex_doc/retriever.ex | 95 ++++++++++++++++++++--------------------- 1 file changed, 46 insertions(+), 49 deletions(-) diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index cdb550ab5..47d1cfcc4 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -144,9 +144,11 @@ defmodule ExDoc.Retriever do moduledoc_groups = Map.get(metadata, :groups, []) - {docs_groups, docs} = + docs_groups = get_docs_groups(moduledoc_groups ++ config.docs_groups ++ module_data.default_groups, docs) + docs = Enum.map(docs, &Map.put(&1, :group, &1.group.title)) + metadata = Map.put(metadata, :kind, module_data.type) group = GroupMatcher.match_module(config.groups_for_modules, module, module_data.id, metadata) {nested_title, nested_context} = module_data.nesting_info || {nil, nil} @@ -204,54 +206,6 @@ defmodule ExDoc.Retriever do filter_defaults(nodes) end - defp get_docs_groups(module_groups, doc_nodes) do - module_groups = Enum.map(module_groups, &normalize_group/1) - - # Doc nodes already have normalized groups - nodes_groups = Enum.map(doc_nodes, & &1.group) - nodes_groups_descriptions = Map.new(nodes_groups, &{&1.title, &1.description}) - - normal_groups = module_groups ++ nodes_groups - - {docs_groups, _} = - Enum.flat_map_reduce(normal_groups, %{}, fn - group, seen when is_map_key(seen, group.title) -> - {[], seen} - - group, seen -> - seen = Map.put(seen, group.title, group.description) - - group = - case group do - %{description: nil} -> - description = Map.get(nodes_groups_descriptions, group.title, nil) - Map.put(group, :description, description) - - _ -> - group - end - - {[group], seen} - end) - - docs_groups = - Enum.map(docs_groups, fn group -> - doc_ast = - case group.description do - nil -> nil - text -> doc_ast("text/markdown", %{"en" => text}, []) - end - - Map.merge(group, %{doc: doc_ast, rendered_doc: nil}) - end) - - # We do not need the full group data in each doc node anymore, only the - # title. - doc_nodes = Enum.map(doc_nodes, &Map.put(&1, :group, &1.group.title)) - - {docs_groups, doc_nodes} - end - defp get_doc(doc, doc_data, module_data, source, group_for_doc, annotations_for_docs) do {:docs_v1, _, _, content_type, _, module_metadata, _} = module_data.docs {{type, name, arity}, anno, _signature, source_doc, metadata} = doc @@ -315,6 +269,49 @@ defmodule ExDoc.Retriever do end) end + defp get_docs_groups(module_groups, doc_nodes) do + module_groups = Enum.map(module_groups, &normalize_group/1) + + # Doc nodes already have normalized groups + nodes_groups = Enum.map(doc_nodes, & &1.group) + nodes_groups_descriptions = Map.new(nodes_groups, &{&1.title, &1.description}) + + normal_groups = module_groups ++ nodes_groups + + {docs_groups, _} = + Enum.flat_map_reduce(normal_groups, %{}, fn + group, seen when is_map_key(seen, group.title) -> + {[], seen} + + group, seen -> + seen = Map.put(seen, group.title, true) + group = finalize_group(group, nodes_groups_descriptions) + {[group], seen} + end) + + docs_groups + end + + defp finalize_group(group, description_fallbacks) do + description = + case group.description do + nil -> Map.get(description_fallbacks, group.title) + text -> text + end + + doc_ast = + case description do + nil -> nil + text -> doc_ast("text/markdown", %{"en" => text}, []) + end + + Map.merge(group, %{ + description: description, + doc: doc_ast, + rendered_doc: nil + }) + end + ## General helpers defp nil_or_name(name, arity) do From a000c6cf97a6187f2ec813c1e683e645cccc2acc Mon Sep 17 00:00:00 2001 From: lud Date: Thu, 17 Apr 2025 06:46:18 +0200 Subject: [PATCH 5/8] use new struct for node group --- lib/ex_doc/nodes.ex | 23 +++++++++++++---------- lib/ex_doc/retriever.ex | 5 +++-- 2 files changed, 16 insertions(+), 12 deletions(-) diff --git a/lib/ex_doc/nodes.ex b/lib/ex_doc/nodes.ex index 12732163b..4997bde99 100644 --- a/lib/ex_doc/nodes.ex +++ b/lib/ex_doc/nodes.ex @@ -27,14 +27,6 @@ defmodule ExDoc.ModuleNode do @typep annotation :: atom() - # TODO: Maybe this is worth its own module - @type doc_group :: %{ - title: String.t() | atom(), - description: String.t() | nil, - doc: ExDoc.DocAST.t() | nil, - rendered_doc: String.t() | nil - } - @type t :: %__MODULE__{ id: String.t(), title: String.t(), @@ -51,7 +43,7 @@ defmodule ExDoc.ModuleNode do moduledoc_file: String.t(), source_path: String.t() | nil, source_url: String.t() | nil, - docs_groups: [doc_group], + docs_groups: [ExDoc.DocGroupNode.t()], docs: [ExDoc.DocNode.t()], typespecs: [ExDoc.DocNode.t()], type: atom(), @@ -97,9 +89,20 @@ defmodule ExDoc.DocNode do signature: String.t(), specs: [ExDoc.Language.spec_ast()], annotations: [annotation()], - group: String.t() | ExDoc.ModuleNode.doc_group() | nil, + group: String.t() | ExDoc.DocGroupNode.t() | nil, doc_file: String.t(), doc_line: non_neg_integer(), source_url: String.t() | nil } end + +defmodule ExDoc.DocGroupNode do + defstruct title: nil, description: nil, doc: nil, rendered_doc: nil + + @type t :: %__MODULE__{ + title: String.t() | atom(), + description: String.t() | nil, + doc: ExDoc.DocAST.t() | nil, + rendered_doc: String.t() | nil + } +end diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 47d1cfcc4..ce73ac3e8 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -305,11 +305,12 @@ defmodule ExDoc.Retriever do text -> doc_ast("text/markdown", %{"en" => text}, []) end - Map.merge(group, %{ + %ExDoc.DocGroupNode{ + title: group.title, description: description, doc: doc_ast, rendered_doc: nil - }) + } end ## General helpers From 8db2c3960f0f9924b13ac309b930c6f8876aa52a Mon Sep 17 00:00:00 2001 From: lud Date: Thu, 17 Apr 2025 06:47:25 +0200 Subject: [PATCH 6/8] enforce group titles as binaries --- lib/ex_doc/retriever.ex | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index ce73ac3e8..ad74b5fa0 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -371,14 +371,14 @@ defmodule ExDoc.Retriever do case group do %{title: title, description: description} when is_binary(title) and (is_binary(description) or is_nil(description)) -> - group + %{group | title: title, description: description} kw when is_list(kw) -> true = Keyword.keyword?(kw) - %{title: Keyword.fetch!(kw, :title), description: kw[:description]} + %{title: to_string(Keyword.fetch!(kw, :title)), description: kw[:description]} title when is_binary(title) when is_atom(title) -> - %{title: title, description: nil} + %{title: to_string(title), description: nil} end end end From b5fcc4d5956edd60181148d5a6aea6dd4d8abf4d Mon Sep 17 00:00:00 2001 From: lud Date: Thu, 17 Apr 2025 07:43:55 +0200 Subject: [PATCH 7/8] do not store groups in DocNode temporarily --- lib/ex_doc/nodes.ex | 2 +- lib/ex_doc/retriever.ex | 26 +++++++++++++++----------- 2 files changed, 16 insertions(+), 12 deletions(-) diff --git a/lib/ex_doc/nodes.ex b/lib/ex_doc/nodes.ex index 4997bde99..0076bd669 100644 --- a/lib/ex_doc/nodes.ex +++ b/lib/ex_doc/nodes.ex @@ -89,7 +89,7 @@ defmodule ExDoc.DocNode do signature: String.t(), specs: [ExDoc.Language.spec_ast()], annotations: [annotation()], - group: String.t() | ExDoc.DocGroupNode.t() | nil, + group: String.t() | nil, doc_file: String.t(), doc_line: non_neg_integer(), source_url: String.t() | nil diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index ad74b5fa0..304a20f13 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -140,14 +140,15 @@ defmodule ExDoc.Retriever do group_for_doc = config.group_for_doc annotations_for_docs = config.annotations_for_docs - docs = get_docs(module_data, source, group_for_doc, annotations_for_docs) + {docs, docs_groups} = get_docs(module_data, source, group_for_doc, annotations_for_docs) moduledoc_groups = Map.get(metadata, :groups, []) docs_groups = - get_docs_groups(moduledoc_groups ++ config.docs_groups ++ module_data.default_groups, docs) - - docs = Enum.map(docs, &Map.put(&1, :group, &1.group.title)) + get_docs_groups( + moduledoc_groups ++ config.docs_groups ++ module_data.default_groups, + docs_groups + ) metadata = Map.put(metadata, :kind, module_data.type) group = GroupMatcher.match_module(config.groups_for_modules, module, module_data.id, metadata) @@ -197,13 +198,15 @@ defmodule ExDoc.Retriever do defp get_docs(module_data, source, group_for_doc, annotations_for_docs) do {:docs_v1, _, _, _, _, _, docs} = module_data.docs - nodes = + {nodes, groups} = for doc <- docs, doc_data = module_data.language.doc_data(doc, module_data) do - get_doc(doc, doc_data, module_data, source, group_for_doc, annotations_for_docs) + {_node, _group} = + get_doc(doc, doc_data, module_data, source, group_for_doc, annotations_for_docs) end + |> Enum.unzip() - filter_defaults(nodes) + {filter_defaults(nodes), groups} end defp get_doc(doc, doc_data, module_data, source, group_for_doc, annotations_for_docs) do @@ -232,7 +235,7 @@ defmodule ExDoc.Retriever do group = normalize_group(group_for_doc.(metadata) || doc_data.default_group) - %ExDoc.DocNode{ + doc_node = %ExDoc.DocNode{ id: doc_data.id_key <> nil_or_name(name, arity), name: name, arity: arity, @@ -246,9 +249,11 @@ defmodule ExDoc.Retriever do specs: doc_data.specs, source_url: source_url, type: doc_data.type, - group: group, + group: group.title, annotations: annotations } + + {doc_node, group} end defp get_defaults(_name, _arity, 0), do: [] @@ -269,11 +274,10 @@ defmodule ExDoc.Retriever do end) end - defp get_docs_groups(module_groups, doc_nodes) do + defp get_docs_groups(module_groups, nodes_groups) do module_groups = Enum.map(module_groups, &normalize_group/1) # Doc nodes already have normalized groups - nodes_groups = Enum.map(doc_nodes, & &1.group) nodes_groups_descriptions = Map.new(nodes_groups, &{&1.title, &1.description}) normal_groups = module_groups ++ nodes_groups From aed460eef09aef4c560f37593b7d893feebe1e01 Mon Sep 17 00:00:00 2001 From: lud Date: Thu, 17 Apr 2025 08:37:24 +0200 Subject: [PATCH 8/8] compute grouped docs summary in retriever --- .../epub/templates/module_template.eex | 6 +-- lib/ex_doc/formatter/html.ex | 41 +++++++++---------- lib/ex_doc/formatter/html/templates.ex | 16 ++------ .../html/templates/module_template.eex | 6 +-- lib/ex_doc/group_matcher.ex | 17 -------- lib/ex_doc/nodes.ex | 7 ++-- lib/ex_doc/retriever.ex | 26 ++++++++---- test/ex_doc/group_matcher_test.exs | 10 ----- test/ex_doc/retriever/erlang_test.exs | 4 +- test/ex_doc/retriever_test.exs | 9 +--- 10 files changed, 54 insertions(+), 88 deletions(-) diff --git a/lib/ex_doc/formatter/epub/templates/module_template.eex b/lib/ex_doc/formatter/epub/templates/module_template.eex index a6c9e1c38..2242051de 100644 --- a/lib/ex_doc/formatter/epub/templates/module_template.eex +++ b/lib/ex_doc/formatter/epub/templates/module_template.eex @@ -18,11 +18,11 @@ <%= if summary != [] do %>

Summary

- <%= for {group, nodes} <- summary, do: H.summary_template(group.title, nodes) %> + <%= for group <- summary, do: H.summary_template(group.title, group.docs) %>
<% end %> - <%= for {group, nodes} <- summary, key = text_to_id(group.title) do %> + <%= for group <- summary, key = text_to_id(group.title) do %>

<%=h to_string(group.title) %>

<%= if doc = group.rendered_doc do %> @@ -31,7 +31,7 @@
<% end %>
- <%= for node <- nodes, do: H.detail_template(node, module) %> + <%= for node <- group.docs, do: H.detail_template(node, module) %>
<% end %> diff --git a/lib/ex_doc/formatter/html.ex b/lib/ex_doc/formatter/html.ex index 30db0e0d2..e7584367c 100644 --- a/lib/ex_doc/formatter/html.ex +++ b/lib/ex_doc/formatter/html.ex @@ -93,33 +93,32 @@ defmodule ExDoc.Formatter.HTML do language: language ] ++ base - docs = - for child_node <- node.docs do - id = id(node, child_node) - - autolink_opts = - autolink_opts ++ - [ - id: id, - line: child_node.doc_line, - file: child_node.doc_file, - current_kfa: {child_node.type, child_node.name, child_node.arity} - ] - - specs = Enum.map(child_node.specs, &language.autolink_spec(&1, autolink_opts)) - child_node = %{child_node | specs: specs} - render_doc(child_node, language, autolink_opts, opts) - end - docs_groups = for group <- node.docs_groups do - render_doc(group, language, autolink_opts, opts) + docs = + for child_node <- group.docs do + id = id(node, child_node) + + autolink_opts = + autolink_opts ++ + [ + id: id, + line: child_node.doc_line, + file: child_node.doc_file, + current_kfa: {child_node.type, child_node.name, child_node.arity} + ] + + specs = Enum.map(child_node.specs, &language.autolink_spec(&1, autolink_opts)) + child_node = %{child_node | specs: specs} + render_doc(child_node, language, autolink_opts, opts) + end + + %{render_doc(group, language, autolink_opts, opts) | docs: docs} end %{ render_doc(node, language, [{:id, node.id} | autolink_opts], opts) - | docs: docs, - docs_groups: docs_groups + | docs_groups: docs_groups } end, timeout: :infinity diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex index 35f18e94b..de6897b9c 100644 --- a/lib/ex_doc/formatter/html/templates.ex +++ b/lib/ex_doc/formatter/html/templates.ex @@ -115,9 +115,9 @@ defmodule ExDoc.Formatter.HTML.Templates do {id, modules} end - defp sidebar_entries({group, nodes}) do + defp sidebar_entries(group) do nodes = - for node <- nodes do + for node <- group.docs do id = if "struct" in node.annotations do node.signature @@ -167,17 +167,7 @@ defmodule ExDoc.Formatter.HTML.Templates do |> Enum.map(&%{id: &1, anchor: URI.encode(text_to_id(&1))}) end - def module_summary(module_node) do - # TODO: Maybe it should be moved to retriever and it already returned grouped metadata - - group_titles = Enum.map(module_node.docs_groups, & &1.title) - groups_index = Map.new(module_node.docs_groups, &{&1.title, &1}) - docs_groups = ExDoc.GroupMatcher.group_by(group_titles, module_node.docs, & &1.group) - - Enum.map(docs_groups, fn {group_title, nodes} -> - {Map.fetch!(groups_index, group_title), nodes} - end) - end + def module_summary(module_node), do: module_node.docs_groups defp favicon_path(%{favicon: nil}), do: nil defp favicon_path(%{favicon: favicon}), do: "assets/favicon#{Path.extname(favicon)}" diff --git a/lib/ex_doc/formatter/html/templates/module_template.eex b/lib/ex_doc/formatter/html/templates/module_template.eex index d785fd914..944b746d3 100644 --- a/lib/ex_doc/formatter/html/templates/module_template.eex +++ b/lib/ex_doc/formatter/html/templates/module_template.eex @@ -39,11 +39,11 @@ Summary - <%= for {group, nodes} <- summary, do: summary_template(group.title, nodes) %> + <%= for group <- summary, do: summary_template(group.title, group.docs) %> <% end %> -<%= for {group, nodes} <- summary, key = text_to_id(group.title) do %> +<%= for group <- summary, key = text_to_id(group.title) do %>

@@ -57,7 +57,7 @@ <% end %>
- <%= for node <- nodes, do: detail_template(node, module) %> + <%= for node <- group.docs, do: detail_template(node, module) %>

<% end %> diff --git a/lib/ex_doc/group_matcher.ex b/lib/ex_doc/group_matcher.ex index 1bdbbd6c1..1ba306f11 100644 --- a/lib/ex_doc/group_matcher.ex +++ b/lib/ex_doc/group_matcher.ex @@ -14,23 +14,6 @@ defmodule ExDoc.GroupMatcher do Enum.find_index(groups, fn {k, _v} -> k == group end) || -1 end - @doc """ - Group the following entries while preserving the order in `groups`. - """ - def group_by(groups, entries, by) do - entries = Enum.group_by(entries, by) - - {groups, leftovers} = - Enum.flat_map_reduce(groups, entries, fn group, grouped_nodes -> - case Map.pop(grouped_nodes, group, []) do - {[], grouped_nodes} -> {[], grouped_nodes} - {entries, grouped_nodes} -> {[{group, entries}], grouped_nodes} - end - end) - - groups ++ Enum.sort(leftovers) - end - @doc """ Finds a matching group for the given module name, id, and metadata. """ diff --git a/lib/ex_doc/nodes.ex b/lib/ex_doc/nodes.ex index 0076bd669..38d9d5750 100644 --- a/lib/ex_doc/nodes.ex +++ b/lib/ex_doc/nodes.ex @@ -87,7 +87,7 @@ defmodule ExDoc.DocNode do rendered_doc: String.t() | nil, type: atom(), signature: String.t(), - specs: [ExDoc.Language.spec_ast()], + specs: [ExDoc.Language.spec_ast() | String.t()], annotations: [annotation()], group: String.t() | nil, doc_file: String.t(), @@ -97,12 +97,13 @@ defmodule ExDoc.DocNode do end defmodule ExDoc.DocGroupNode do - defstruct title: nil, description: nil, doc: nil, rendered_doc: nil + defstruct title: nil, description: nil, doc: nil, rendered_doc: nil, docs: [] @type t :: %__MODULE__{ title: String.t() | atom(), description: String.t() | nil, doc: ExDoc.DocAST.t() | nil, - rendered_doc: String.t() | nil + rendered_doc: String.t() | nil, + docs: [ExDoc.DocNode.t()] } end diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 304a20f13..5b308b38c 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -140,14 +140,16 @@ defmodule ExDoc.Retriever do group_for_doc = config.group_for_doc annotations_for_docs = config.annotations_for_docs - {docs, docs_groups} = get_docs(module_data, source, group_for_doc, annotations_for_docs) + {docs, nodes_groups} = get_docs(module_data, source, group_for_doc, annotations_for_docs) + docs = ExDoc.Utils.natural_sort_by(docs, &"#{&1.name}/#{&1.arity}") moduledoc_groups = Map.get(metadata, :groups, []) docs_groups = get_docs_groups( moduledoc_groups ++ config.docs_groups ++ module_data.default_groups, - docs_groups + nodes_groups, + docs ) metadata = Map.put(metadata, :kind, module_data.type) @@ -164,7 +166,7 @@ defmodule ExDoc.Retriever do type: module_data.type, deprecated: metadata[:deprecated], docs_groups: docs_groups, - docs: ExDoc.Utils.natural_sort_by(docs, &"#{&1.name}/#{&1.arity}"), + docs: docs, doc_format: format, doc: doc, source_doc: source_doc, @@ -274,13 +276,14 @@ defmodule ExDoc.Retriever do end) end - defp get_docs_groups(module_groups, nodes_groups) do + defp get_docs_groups(module_groups, nodes_groups, doc_nodes) do module_groups = Enum.map(module_groups, &normalize_group/1) # Doc nodes already have normalized groups nodes_groups_descriptions = Map.new(nodes_groups, &{&1.title, &1.description}) normal_groups = module_groups ++ nodes_groups + nodes_by_group_title = Enum.group_by(doc_nodes, & &1.group) {docs_groups, _} = Enum.flat_map_reduce(normal_groups, %{}, fn @@ -289,14 +292,21 @@ defmodule ExDoc.Retriever do group, seen -> seen = Map.put(seen, group.title, true) - group = finalize_group(group, nodes_groups_descriptions) - {[group], seen} + + case Map.get(nodes_by_group_title, group.title, []) do + [] -> + {[], seen} + + child_nodes -> + group = finalize_group(group, child_nodes, nodes_groups_descriptions) + {[group], seen} + end end) docs_groups end - defp finalize_group(group, description_fallbacks) do + defp finalize_group(group, doc_nodes, description_fallbacks) do description = case group.description do nil -> Map.get(description_fallbacks, group.title) @@ -313,7 +323,7 @@ defmodule ExDoc.Retriever do title: group.title, description: description, doc: doc_ast, - rendered_doc: nil + docs: doc_nodes } end diff --git a/test/ex_doc/group_matcher_test.exs b/test/ex_doc/group_matcher_test.exs index 9f5832570..a73f4363d 100644 --- a/test/ex_doc/group_matcher_test.exs +++ b/test/ex_doc/group_matcher_test.exs @@ -2,16 +2,6 @@ defmodule ExDoc.GroupMatcherTest do use ExUnit.Case, async: true import ExDoc.GroupMatcher - describe "group_by" do - test "group by given data with leftovers" do - assert group_by([1, 3, 5], [%{key: 1}, %{key: 3}, %{key: 2}], & &1.key) == [ - {1, [%{key: 1}]}, - {3, [%{key: 3}]}, - {2, [%{key: 2}]} - ] - end - end - describe "module matching" do test "by atom names" do patterns = [ diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs index 94f43925a..56f10126f 100644 --- a/test/ex_doc/retriever/erlang_test.exs +++ b/test/ex_doc/retriever/erlang_test.exs @@ -59,7 +59,7 @@ defmodule ExDoc.Retriever.ErlangTest do moduledoc_line: 2, moduledoc_file: moduledoc_file, docs: [equiv_function2, function1, function2], - docs_groups: [%{title: "Types"}, %{title: "Callbacks"}, %{title: "Functions"}], + docs_groups: [%{title: "Functions"}], group: nil, id: "mod", language: ExDoc.Language.Erlang, @@ -397,7 +397,7 @@ defmodule ExDoc.Retriever.ErlangTest do deprecated: nil, moduledoc_line: _, docs: [function1, function2], - docs_groups: [%{title: "Types"}, %{title: "Callbacks"}, %{title: "Functions"}], + docs_groups: [%{title: "Functions"}], group: nil, id: "mod", language: ExDoc.Language.Erlang, diff --git a/test/ex_doc/retriever_test.exs b/test/ex_doc/retriever_test.exs index 9c8eca5b6..243726d33 100644 --- a/test/ex_doc/retriever_test.exs +++ b/test/ex_doc/retriever_test.exs @@ -140,7 +140,7 @@ defmodule ExDoc.RetrieverTest do {[mod], []} = Retriever.docs_from_modules([A], config) - assert [c, b, types, callbacks, functions, a] = mod.docs_groups + assert [c, b, a] = mod.docs_groups # Description returned by the function should override nil assert %{title: "c", description: "for c"} = c @@ -149,10 +149,6 @@ defmodule ExDoc.RetrieverTest do # description from @moduledoc assert %{title: "b", description: "predefined b"} = b - assert %{title: "Types", description: nil} = types - assert %{title: "Callbacks", description: nil} = callbacks - assert %{title: "Functions", description: nil} = functions - # Description returned by th function should define a description # for leftover groups assert %{title: "a", description: "for a"} = a @@ -189,9 +185,6 @@ defmodule ExDoc.RetrieverTest do assert [ %{description: nil, title: "c"}, %{description: "text for b", title: "b"}, - %{description: nil, title: "Types"}, - %{description: nil, title: "Callbacks"}, - %{description: nil, title: "Functions"}, %{description: nil, title: "a"} ] = mod.docs_groups end