From c6e237a63236eb71a3bc732b3cd6aca99d8c44f7 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Thu, 2 Oct 2025 17:09:16 -0400 Subject: [PATCH 01/33] feat: add Markdown formatter Signed-off-by: Yordis Prieto --- lib/ex_doc/doc_ast.ex | 71 ++++++ lib/ex_doc/formatter.ex | 23 +- lib/ex_doc/formatter/markdown.ex | 211 ++++++++++++++++++ lib/ex_doc/formatter/markdown/templates.ex | 169 ++++++++++++++ .../markdown/templates/detail_template.eex | 17 ++ .../markdown/templates/module_template.eex | 36 +++ .../templates/nav_grouped_item_template.eex | 8 + .../markdown/templates/nav_item_template.eex | 6 + .../markdown/templates/nav_template.eex | 9 + .../markdown/templates/summary_template.eex | 15 ++ test/ex_doc/formatter/markdown_test.exs | 133 +++++++++++ 11 files changed, 690 insertions(+), 8 deletions(-) create mode 100644 lib/ex_doc/formatter/markdown.ex create mode 100644 lib/ex_doc/formatter/markdown/templates.ex create mode 100644 lib/ex_doc/formatter/markdown/templates/detail_template.eex create mode 100644 lib/ex_doc/formatter/markdown/templates/module_template.eex create mode 100644 lib/ex_doc/formatter/markdown/templates/nav_grouped_item_template.eex create mode 100644 lib/ex_doc/formatter/markdown/templates/nav_item_template.eex create mode 100644 lib/ex_doc/formatter/markdown/templates/nav_template.eex create mode 100644 lib/ex_doc/formatter/markdown/templates/summary_template.eex create mode 100644 test/ex_doc/formatter/markdown_test.exs diff --git a/lib/ex_doc/doc_ast.ex b/lib/ex_doc/doc_ast.ex index ed84cfd2c..7049c7ddf 100644 --- a/lib/ex_doc/doc_ast.ex +++ b/lib/ex_doc/doc_ast.ex @@ -65,6 +65,77 @@ defmodule ExDoc.DocAST do Enum.map(attrs, fn {key, val} -> " #{key}=\"#{ExDoc.Utils.h(val)}\"" end) end + @doc """ + Transform AST into markdown string. + + The optional `fun` argument allows post-processing each AST node + after it's been converted to markdown. + """ + def to_markdown_string(ast, fun \\ fn _ast, string -> string end) + + def to_markdown_string(binary, _fun) when is_binary(binary) do + ExDoc.Utils.h(binary) + end + + def to_markdown_string(list, fun) when is_list(list) do + result = Enum.map_join(list, "", &to_markdown_string(&1, fun)) + fun.(list, result) + end + + def to_markdown_string({:comment, _attrs, inner, _meta} = ast, fun) do + fun.(ast, "") + end + + def to_markdown_string({:code, attrs, inner, _meta} = ast, fun) do + lang = attrs[:class] || "" + + result = """ + ```#{lang} + #{inner} + ``` + """ + + fun.(ast, result) + end + + def to_markdown_string({:a, attrs, inner, _meta} = ast, fun) do + result = "[#{to_markdown_string(inner, fun)}](#{attrs[:href]})" + fun.(ast, result) + end + + def to_markdown_string({:hr, _attrs, _inner, _meta} = ast, fun) do + result = "\n\n---\n\n" + fun.(ast, result) + end + + def to_markdown_string({tag, _attrs, _inner, _meta} = ast, fun) when tag in [:p, :br] do + result = "\n\n" + fun.(ast, result) + end + + def to_markdown_string({:img, attrs, _inner, _meta} = ast, fun) do + alt = attrs[:alt] || "" + title = attrs[:title] || "" + result = "![#{alt}](#{attrs[:src]} \"#{title}\")" + fun.(ast, result) + end + + # ignoring these: area base col command embed input keygen link meta param source track wbr + def to_markdown_string({tag, _attrs, _inner, _meta} = ast, fun) when tag in @void_elements do + result = "" + fun.(ast, result) + end + + def to_markdown_string({_tag, _attrs, inner, %{verbatim: true}} = ast, fun) do + result = Enum.join(inner, "") + fun.(ast, result) + end + + def to_markdown_string({_tag, _attrs, inner, _meta} = ast, fun) do + result = to_markdown_string(inner, fun) + fun.(ast, result) + end + ## parse markdown defp parse_markdown(markdown, opts) do diff --git a/lib/ex_doc/formatter.ex b/lib/ex_doc/formatter.ex index f8f4b2eee..3c8b20b24 100644 --- a/lib/ex_doc/formatter.ex +++ b/lib/ex_doc/formatter.ex @@ -48,14 +48,14 @@ defmodule ExDoc.Formatter do 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) + render_doc(child_node, ext, language, autolink_opts, opts) end - %{render_doc(group, language, autolink_opts, opts) | docs: docs} + %{render_doc(group, ext, language, autolink_opts, opts) | docs: docs} end %{ - render_doc(node, language, [{:id, node.id} | autolink_opts], opts) + render_doc(node, ext, language, [{:id, node.id} | autolink_opts], opts) | docs_groups: docs_groups } end, @@ -117,11 +117,11 @@ defmodule ExDoc.Formatter do # Helper functions - defp render_doc(%{doc: nil} = node, _language, _autolink_opts, _opts), + defp render_doc(%{doc: nil} = node, _ext, _language, _autolink_opts, _opts), do: node - defp render_doc(%{doc: doc} = node, language, autolink_opts, opts) do - doc = autolink_and_highlight(doc, language, autolink_opts, opts) + defp render_doc(%{doc: doc} = node, ext, language, autolink_opts, opts) do + doc = autolink_and_render(doc, ext, language, autolink_opts, opts) %{node | doc: doc} end @@ -137,7 +137,13 @@ defmodule ExDoc.Formatter do mod_id <> "." <> id end - defp autolink_and_highlight(doc, language, autolink_opts, opts) do + defp autolink_and_render(doc, ".md", language, autolink_opts, _opts) do + doc + |> language.autolink_doc(autolink_opts) + |> ExDoc.DocAST.to_markdown_string() + end + + defp autolink_and_render(doc, _html_ext, language, autolink_opts, opts) do doc |> language.autolink_doc(autolink_opts) |> ExDoc.DocAST.highlight(language, opts) @@ -187,6 +193,7 @@ defmodule ExDoc.Formatter do source_file = validate_extra_string!(input_options, :source) || input opts = [file: source_file, line: 1] + ext = Keyword.fetch!(autolink_opts, :ext) {extension, source, ast} = case extension_name(input) do @@ -202,7 +209,7 @@ defmodule ExDoc.Formatter do source |> Markdown.to_ast(opts) |> ExDoc.DocAST.add_ids_to_headers([:h2, :h3]) - |> autolink_and_highlight(language, [file: input] ++ autolink_opts, opts) + |> autolink_and_render(ext, language, [file: input] ++ autolink_opts, opts) {extension, source, ast} diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex new file mode 100644 index 000000000..8f8883485 --- /dev/null +++ b/lib/ex_doc/formatter/markdown.ex @@ -0,0 +1,211 @@ +defmodule ExDoc.Formatter.MARKDOWN do + @moduledoc false + + alias __MODULE__.{Templates} + alias ExDoc.Formatter + alias ExDoc.Utils + + @doc """ + Generates Markdown documentation for the given modules. + """ + @spec run([ExDoc.ModuleNode.t()], [ExDoc.ModuleNode.t()], ExDoc.Config.t()) :: String.t() + def run(project_nodes, filtered_modules, config) when is_map(config) do + Utils.unset_warned() + + config = normalize_config(config) + File.rm_rf!(config.output) + File.mkdir_p!(config.output) + + extras = Formatter.build_extras(config, ".md") + + project_nodes = + project_nodes + |> Formatter.render_all(filtered_modules, ".md", config, highlight_tag: "samp") + + nodes_map = %{ + modules: Formatter.filter_list(:module, project_nodes), + tasks: Formatter.filter_list(:task, project_nodes) + } + + config = %{config | extras: extras} + + generate_nav(config, nodes_map) + generate_extras(config) + generate_list(config, nodes_map.modules) + generate_list(config, nodes_map.tasks) + generate_llm_index(config, nodes_map) + + config.output |> Path.join("index.md") |> Path.relative_to_cwd() + end + + defp normalize_config(config) do + output = + config.output + |> Path.expand() + |> Path.join("markdown") + + %{config | output: output} + end + + defp normalize_output(output) do + output + |> String.replace(~r/\r\n|\r|\n/, "\n") + |> String.replace(~r/\n{3,}/, "\n\n") + end + + defp generate_nav(config, nodes) do + nodes = + Map.update!(nodes, :modules, fn modules -> + modules |> Enum.chunk_by(& &1.group) |> Enum.map(&{hd(&1).group, &1}) + end) + + content = + Templates.nav_template(config, nodes) + |> normalize_output() + + File.write("#{config.output}/index.md", content) + end + + defp generate_extras(config) do + for {_title, extras} <- config.extras do + Enum.each(extras, fn %{id: id, source: content} -> + output = "#{config.output}/#{id}.md" + + if File.regular?(output) do + Utils.warn("file #{Path.relative_to_cwd(output)} already exists", []) + end + + File.write!(output, normalize_output(content)) + end) + end + end + + defp generate_list(config, nodes) do + nodes + |> Task.async_stream(&generate_module_page(&1, config), timeout: :infinity) + |> Enum.map(&elem(&1, 1)) + end + + ## Helpers + + defp generate_module_page(module_node, config) do + content = + Templates.module_page(config, module_node) + |> normalize_output() + + File.write("#{config.output}/#{module_node.id}.md", content) + end + + defp generate_llm_index(config, nodes_map) do + content = generate_llm_index_content(config, nodes_map) + File.write("#{config.output}/llms.txt", content) + end + + defp generate_llm_index_content(config, nodes_map) do + project_info = """ + # #{config.project} #{config.version} + + #{config.project} documentation index for Large Language Models. + + ## Modules + + """ + + modules_info = + nodes_map.modules + |> Enum.map(fn module_node -> + "- **#{module_node.title}** (#{module_node.id}.md): #{module_node.doc |> extract_summary()}" + end) + |> Enum.join("\n") + + tasks_info = + if length(nodes_map.tasks) > 0 do + tasks_list = + nodes_map.tasks + |> Enum.map(fn task_node -> + "- **#{task_node.title}** (#{task_node.id}.md): #{task_node.doc |> extract_summary()}" + end) + |> Enum.join("\n") + + "\n\n## Mix Tasks\n\n" <> tasks_list + else + "" + end + + extras_info = + if is_list(config.extras) and length(config.extras) > 0 do + extras_list = + config.extras + |> Enum.flat_map(fn + {_group, extras} when is_list(extras) -> extras + _ -> [] + end) + |> Enum.map(fn extra -> + "- **#{extra.title}** (#{extra.id}.md): #{extra.title}" + end) + |> Enum.join("\n") + + if extras_list == "" do + "" + else + "\n\n## Guides\n\n" <> extras_list + end + else + "" + end + + project_info <> modules_info <> tasks_info <> extras_info + end + + defp extract_summary(nil), do: "No documentation available" + defp extract_summary(""), do: "No documentation available" + + defp extract_summary(doc) when is_binary(doc) do + doc + |> String.split("\n") + |> Enum.find("", fn line -> String.trim(line) != "" end) + |> String.trim() + |> case do + "" -> + "No documentation available" + + summary -> + summary + |> String.slice(0, 150) + |> then(fn s -> if String.length(s) == 150, do: s <> "...", else: s end) + end + end + + defp extract_summary(doc_ast) when is_list(doc_ast) do + # For DocAST (which is a list), extract the first text node + extract_first_text_from_ast(doc_ast) + end + + defp extract_summary(_), do: "No documentation available" + + defp extract_first_text_from_ast([]), do: "No documentation available" + + defp extract_first_text_from_ast([{:p, _, content} | _rest]) do + extract_text_from_content(content) + |> String.slice(0, 150) + |> then(fn s -> if String.length(s) == 150, do: s <> "...", else: s end) + end + + defp extract_first_text_from_ast([_node | rest]) do + extract_first_text_from_ast(rest) + end + + defp extract_text_from_content([]), do: "" + defp extract_text_from_content([text | _rest]) when is_binary(text), do: text + + defp extract_text_from_content([{_tag, _attrs, content} | rest]) do + case extract_text_from_content(content) do + "" -> extract_text_from_content(rest) + text -> text + end + end + + defp extract_text_from_content([_node | rest]) do + extract_text_from_content(rest) + end +end diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex new file mode 100644 index 000000000..373473e40 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -0,0 +1,169 @@ +defmodule ExDoc.Formatter.MARKDOWN.Templates do + @moduledoc false + + require EEx + + import ExDoc.Utils, + only: [before_closing_body_tag: 2, h: 1, text_to_id: 1] + + @doc """ + Generate content from the module template for a given `node` + """ + def module_page(config, module_node) do + summary = + for group <- module_node.docs_groups do + {group.title, group.docs} + end + + module_template(config, module_node, summary) + end + + @doc """ + Returns the formatted title for the module page. + """ + def module_type(%{type: :task}), do: "" + def module_type(%{type: :module}), do: "" + def module_type(%{type: type}), do: "(#{type})" + + @doc """ + Format the attribute type used to define the spec of the given `node`. + """ + def format_spec_attribute(module, node) do + module.language.format_spec_attribute(node) + end + + @doc """ + Generated ID for static file + """ + def static_file_to_id(static_file) do + static_file |> Path.basename() |> text_to_id() + end + + def node_doc(%{source_doc: %{"en" => source}}) when is_binary(source), do: source + def node_doc(%{rendered_doc: source}) when is_binary(source), do: source + + def node_doc(%{source_doc: %{"en" => source}}) when is_list(source) do + # Handle DocAST by converting to markdown + # For Erlang docs, we can extract text content + extract_text_from_doc_ast(source) + end + + def node_doc(_), do: nil + + defp extract_text_from_doc_ast(ast) when is_list(ast) do + Enum.map_join(ast, "\n\n", &extract_text_from_doc_ast/1) + end + + defp extract_text_from_doc_ast({_tag, _attrs, content}) when is_list(content) do + Enum.map_join(content, "", &extract_text_from_doc_ast/1) + end + + defp extract_text_from_doc_ast({_tag, _attrs, content, _meta}) when is_list(content) do + Enum.map_join(content, "", &extract_text_from_doc_ast/1) + end + + defp extract_text_from_doc_ast(text) when is_binary(text), do: text + defp extract_text_from_doc_ast(_), do: "" + + @doc """ + Gets the first paragraph of the documentation of a node. It strips + surrounding white-spaces and trailing `:`. + + If `doc` is `nil`, it returns `nil`. + """ + @spec synopsis(String.t()) :: String.t() + @spec synopsis(nil) :: nil + def synopsis(doc) when is_binary(doc) do + case :binary.split(doc, "\n\n") do + [left, _] -> String.trim_trailing(left, ": ") <> "\n\n" + [all] -> all + end + end + + def synopsis(_), do: nil + + @heading_regex ~r/^(\#{1,6})\s+(.*)/m + defp rewrite_headings(content) when is_binary(content) do + @heading_regex + |> Regex.scan(content) + |> Enum.reduce(content, fn [match, level, title], content -> + replacement = rewrite_heading(level, title) + String.replace(content, match, replacement, global: false) + end) + end + + defp rewrite_headings(_), do: nil + + defp rewrite_heading("#", title), do: do_rewrite_heading("#####", title) + defp rewrite_heading(_, title), do: do_rewrite_heading("######", title) + + defp do_rewrite_heading(level, title) do + """ + #{level} #{title} + """ + end + + defp enc(binary), do: URI.encode(binary) |> String.replace("/", "-") + + @doc """ + Creates a chapter which contains all the details about an individual module. + + This chapter can include the following sections: *functions*, *types*, *callbacks*. + """ + EEx.function_from_file( + :def, + :module_template, + Path.expand("templates/module_template.eex", __DIR__), + [:config, :module, :summary], + trim: true + ) + + @doc """ + Creates the table of contents. + + """ + EEx.function_from_file( + :def, + :nav_template, + Path.expand("templates/nav_template.eex", __DIR__), + [:config, :nodes], + trim: true + ) + + EEx.function_from_file( + :defp, + :nav_item_template, + Path.expand("templates/nav_item_template.eex", __DIR__), + [:name, :nodes], + trim: true + ) + + EEx.function_from_file( + :defp, + :nav_grouped_item_template, + Path.expand("templates/nav_grouped_item_template.eex", __DIR__), + [:nodes], + trim: true + ) + + # EEx.function_from_file( + # :defp, + # :toc_item_template, + # Path.expand("templates/toc_item_template.eex", __DIR__), + # [:nodes], + # trim: true + # ) + + # def media_type(_arg), do: nil + + templates = [ + detail_template: [:node, :module], + summary_template: [:name, :nodes] + ] + + Enum.each(templates, fn {name, args} -> + filename = Path.expand("templates/#{name}.eex", __DIR__) + @doc false + EEx.function_from_file(:def, name, filename, args, trim: true) + end) +end diff --git a/lib/ex_doc/formatter/markdown/templates/detail_template.eex b/lib/ex_doc/formatter/markdown/templates/detail_template.eex new file mode 100644 index 000000000..937bfe45a --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/detail_template.eex @@ -0,0 +1,17 @@ + +#### `<%=h node.signature %>` <%= if node.source_url do %>[🔗](<%= node.source_url %>)<% end %> <%= for annotation <- node.annotations do %>(<%= annotation %>) <% end %> + +<%= if deprecated = node.deprecated do %> +> This <%= node.type %> is deprecated. <%= h(deprecated) %>. +<% end %> + +<%= if node.specs != [] do %> +<%= for spec <- node.specs do %> +```elixir +<%= format_spec_attribute(module, node) %> <%= spec %> +``` +<% end %> +<% end %> + +<%= rewrite_headings(node_doc(node)) %> + diff --git a/lib/ex_doc/formatter/markdown/templates/module_template.eex b/lib/ex_doc/formatter/markdown/templates/module_template.eex new file mode 100644 index 000000000..c21285350 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/module_template.eex @@ -0,0 +1,36 @@ +# <%= module.title %> <%= module_type(module) %> (<%= config.project %> v<%= config.version %>) + +<%= for annotation <- module.annotations do %>*(<%= annotation %>)* <% end %> + +<%= if deprecated = module.deprecated do %> +> This <%= module.type %> is deprecated. <%=h deprecated %>. +<% end %> + +<%= if doc = node_doc(module) do %> +<%= doc %> +<% end %> + +<%= if summary != [] do %> +## Table of Contents +<%= for {name, nodes} <- summary, do: summary_template(name, nodes) %> +<% end %> + +## Contents + +<%= for {name, nodes} <- summary, _key = text_to_id(name) do %> + +### <%=h to_string(name) %> + +<%= for node <- nodes do %> +<%= detail_template(node, module) %> +<% end %> + +<% end %> + +--- + +<%= if module.source_url do %> +[<%= String.capitalize(to_string(module.type)) %> Source Code](<%= module.source_url %>) +<% end %> + +<%= before_closing_body_tag(config, :markdown) %> diff --git a/lib/ex_doc/formatter/markdown/templates/nav_grouped_item_template.eex b/lib/ex_doc/formatter/markdown/templates/nav_grouped_item_template.eex new file mode 100644 index 000000000..874ebdbfd --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/nav_grouped_item_template.eex @@ -0,0 +1,8 @@ +<%= for {title, nodes} <- nodes do %> +<%= if title do %> +- <%=h to_string(title) %> +<% end %> +<%= for node <- nodes do %> + - [<%=h node.title %>](<%= URI.encode node.id %>.md) +<% end %> +<% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/nav_item_template.eex b/lib/ex_doc/formatter/markdown/templates/nav_item_template.eex new file mode 100644 index 000000000..449c46e22 --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/nav_item_template.eex @@ -0,0 +1,6 @@ +<%= unless Enum.empty?(nodes) do %> +- <%= name %> +<%= for node <- nodes do %> + - [<%=h node.title %>](<%= URI.encode node.id %>.md) +<% end %> +<% end %> diff --git a/lib/ex_doc/formatter/markdown/templates/nav_template.eex b/lib/ex_doc/formatter/markdown/templates/nav_template.eex new file mode 100644 index 000000000..48f11c99a --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/nav_template.eex @@ -0,0 +1,9 @@ +# <%= config.project %> v<%= config.version %> - Documentation - Table of contents + +<%= nav_grouped_item_template config.extras %> +<%= unless Enum.empty?(nodes.modules) do %> +## Modules +<%= nav_grouped_item_template nodes.modules %> +<% end %> +<%= nav_item_template "Mix Tasks", nodes.tasks %> +<%= before_closing_body_tag(config, :markdown) %> diff --git a/lib/ex_doc/formatter/markdown/templates/summary_template.eex b/lib/ex_doc/formatter/markdown/templates/summary_template.eex new file mode 100644 index 000000000..7d8ffcb7b --- /dev/null +++ b/lib/ex_doc/formatter/markdown/templates/summary_template.eex @@ -0,0 +1,15 @@ +### <%= name %> + +<%= for node <- nodes do %> + +#### [`<%=h node.signature %>`](#<%= enc node.id %>) + +<%= if deprecated = node.deprecated do %> +> <%= h(deprecated) %> +<% end %> + +<%= if doc = node_doc(node) do %> +<%= synopsis(doc) %> +<% end %> + +<% end %> diff --git a/test/ex_doc/formatter/markdown_test.exs b/test/ex_doc/formatter/markdown_test.exs new file mode 100644 index 000000000..135f466ac --- /dev/null +++ b/test/ex_doc/formatter/markdown_test.exs @@ -0,0 +1,133 @@ +defmodule ExDoc.Formatter.MARKDOWNTest do + use ExUnit.Case, async: false + + @moduletag :tmp_dir + + defp doc_config(%{tmp_dir: tmp_dir} = _context) do + [ + project: "Elixir", + version: "1.0.1", + formatter: "markdown", + output: tmp_dir, + source_beam: "test/tmp/beam", + skip_undefined_reference_warnings_on: ["Warnings"] + ] + end + + defp doc_config(context, config) when is_map(context) and is_list(config) do + Keyword.merge(doc_config(context), config) + end + + defp generate_docs(config) do + ExDoc.generate_docs(config[:project], config[:version], config) + end + + test "generates markdown files in the default directory", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + assert File.regular?(tmp_dir <> "/markdown/index.md") + assert File.regular?(tmp_dir <> "/markdown/CompiledWithDocs.md") + end + + test "generates headers for module pages", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context, main: "RandomError")) + + content = File.read!(tmp_dir <> "/markdown/RandomError.md") + assert content =~ ~r{^# RandomError}m + assert content =~ ~r{\(Elixir v1\.0\.1\)} + end + + test "generates all listing files", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + + assert File.regular?(tmp_dir <> "/markdown/CompiledWithDocs.md") + assert File.regular?(tmp_dir <> "/markdown/CompiledWithDocs.Nested.md") + assert File.regular?(tmp_dir <> "/markdown/CustomBehaviourOne.md") + assert File.regular?(tmp_dir <> "/markdown/CustomBehaviourTwo.md") + assert File.regular?(tmp_dir <> "/markdown/RandomError.md") + assert File.regular?(tmp_dir <> "/markdown/CustomProtocol.md") + assert File.regular?(tmp_dir <> "/markdown/Mix.Tasks.TaskWithDocs.md") + end + + test "generates the index file", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + + content = File.read!(tmp_dir <> "/markdown/index.md") + assert content =~ ~r{^# Elixir v1\.0\.1 - Documentation - Table of contents$}m + assert content =~ ~r{## Modules} + assert content =~ ~r{- \[CompiledWithDocs\]\(CompiledWithDocs\.md\)} + assert content =~ ~r{- \[CompiledWithDocs\.Nested\]\(CompiledWithDocs\.Nested\.md\)} + end + + test "generates module with proper structure", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + + content = File.read!(tmp_dir <> "/markdown/CompiledWithDocs.md") + + # Header + assert content =~ ~r{^# CompiledWithDocs \(Elixir v1\.0\.1\)}m + assert content =~ ~r{\*\(example_module_tag\)\*} + + # Moduledoc + assert content =~ ~r{moduledoc} + + # Table of Contents + assert content =~ ~r{## Table of Contents} + assert content =~ ~r{### Functions} + + # Contents section + assert content =~ ~r{## Contents} + end + + test "generates functions correctly", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + + content = File.read!(tmp_dir <> "/markdown/CompiledWithDocs.md") + + # Function in ToC + assert content =~ ~r{####.*\[`example\(foo, bar} + assert content =~ ~r{#example-2\)} + + # Function details + assert content =~ ~r{} + assert content =~ ~r{#### `example\(foo, bar \\\\ Baz\)`} + assert content =~ ~r{Some example} + + # Deprecated notice + assert content =~ ~r{> This function is deprecated\. Use something else instead\.} + + # Struct + assert content =~ ~r{`%CompiledWithDocs\{\}`} + assert content =~ ~r{Some struct} + + # Since annotation + assert content =~ ~r{example_1\(\)} + assert content =~ ~r{\(since 1\.3\.0\)} + + # Macro annotation + assert content =~ ~r{\(macro\)} + end + + describe "generates extras" do + test "ignores any external url extras", %{tmp_dir: tmp_dir} = context do + config = + context + |> doc_config() + |> Keyword.put(:extras, elixir: [url: "https://elixir-lang.org"]) + + generate_docs(config) + + refute File.exists?(tmp_dir <> "/markdown/elixir.md") + end + end + + test "generates LLM index file", %{tmp_dir: tmp_dir} = context do + generate_docs(doc_config(context)) + + content = File.read!(tmp_dir <> "/markdown/llms.txt") + + assert content =~ ~r{# Elixir 1\.0\.1} + assert content =~ ~r{Elixir documentation index for Large Language Models} + assert content =~ ~r{## Modules} + assert content =~ ~r{- \*\*CompiledWithDocs\*\* \(CompiledWithDocs\.md\):} + end +end From 7297cd36b4f158e6828a42e855016930d61310e3 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 12:22:44 -0400 Subject: [PATCH 02/33] fix --- lib/ex_doc/formatter/markdown.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex index 8f8883485..d4f3c7be3 100644 --- a/lib/ex_doc/formatter/markdown.ex +++ b/lib/ex_doc/formatter/markdown.ex @@ -49,7 +49,7 @@ defmodule ExDoc.Formatter.MARKDOWN do defp normalize_output(output) do output - |> String.replace(~r/\r\n|\r|\n/, "\n") + |> String.replace(["\r\n", "\n"], "\n") |> String.replace(~r/\n{3,}/, "\n\n") end From 1e5c09fe920d4554a64c3beb6a3881ae25c2de31 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 12:32:10 -0400 Subject: [PATCH 03/33] refactor: rename to_markdown_string to to_markdown and update related function calls --- lib/ex_doc/doc_ast.ex | 36 +++++++++++++--------- lib/ex_doc/formatter.ex | 4 +-- lib/ex_doc/formatter/markdown/templates.ex | 6 ++++ 3 files changed, 29 insertions(+), 17 deletions(-) diff --git a/lib/ex_doc/doc_ast.ex b/lib/ex_doc/doc_ast.ex index 7049c7ddf..bf8601044 100644 --- a/lib/ex_doc/doc_ast.ex +++ b/lib/ex_doc/doc_ast.ex @@ -71,22 +71,22 @@ defmodule ExDoc.DocAST do The optional `fun` argument allows post-processing each AST node after it's been converted to markdown. """ - def to_markdown_string(ast, fun \\ fn _ast, string -> string end) + def to_markdown(ast, fun \\ fn _ast, string -> string end) - def to_markdown_string(binary, _fun) when is_binary(binary) do + def to_markdown(binary, _fun) when is_binary(binary) do ExDoc.Utils.h(binary) end - def to_markdown_string(list, fun) when is_list(list) do - result = Enum.map_join(list, "", &to_markdown_string(&1, fun)) + def to_markdown(list, fun) when is_list(list) do + result = Enum.map_join(list, "", &to_markdown(&1, fun)) fun.(list, result) end - def to_markdown_string({:comment, _attrs, inner, _meta} = ast, fun) do + def to_markdown({:comment, _attrs, inner, _meta} = ast, fun) do fun.(ast, "") end - def to_markdown_string({:code, attrs, inner, _meta} = ast, fun) do + def to_markdown({:code, attrs, inner, _meta} = ast, fun) do lang = attrs[:class] || "" result = """ @@ -98,22 +98,27 @@ defmodule ExDoc.DocAST do fun.(ast, result) end - def to_markdown_string({:a, attrs, inner, _meta} = ast, fun) do - result = "[#{to_markdown_string(inner, fun)}](#{attrs[:href]})" + def to_markdown({:a, attrs, inner, _meta} = ast, fun) do + result = "[#{to_markdown(inner, fun)}](#{attrs[:href]})" fun.(ast, result) end - def to_markdown_string({:hr, _attrs, _inner, _meta} = ast, fun) do + def to_markdown({:hr, _attrs, _inner, _meta} = ast, fun) do result = "\n\n---\n\n" fun.(ast, result) end - def to_markdown_string({tag, _attrs, _inner, _meta} = ast, fun) when tag in [:p, :br] do + def to_markdown({:p, _attrs, inner, _meta} = ast, fun) do + result = to_markdown(inner, fun) <> "\n\n" + fun.(ast, result) + end + + def to_markdown({:br, _attrs, _inner, _meta} = ast, fun) do result = "\n\n" fun.(ast, result) end - def to_markdown_string({:img, attrs, _inner, _meta} = ast, fun) do + def to_markdown({:img, attrs, _inner, _meta} = ast, fun) do alt = attrs[:alt] || "" title = attrs[:title] || "" result = "![#{alt}](#{attrs[:src]} \"#{title}\")" @@ -121,21 +126,22 @@ defmodule ExDoc.DocAST do end # ignoring these: area base col command embed input keygen link meta param source track wbr - def to_markdown_string({tag, _attrs, _inner, _meta} = ast, fun) when tag in @void_elements do + def to_markdown({tag, _attrs, _inner, _meta} = ast, fun) when tag in @void_elements do result = "" fun.(ast, result) end - def to_markdown_string({_tag, _attrs, inner, %{verbatim: true}} = ast, fun) do + def to_markdown({_tag, _attrs, inner, %{verbatim: true}} = ast, fun) do result = Enum.join(inner, "") fun.(ast, result) end - def to_markdown_string({_tag, _attrs, inner, _meta} = ast, fun) do - result = to_markdown_string(inner, fun) + def to_markdown({_tag, _attrs, inner, _meta} = ast, fun) do + result = to_markdown(inner, fun) fun.(ast, result) end + ## parse markdown defp parse_markdown(markdown, opts) do diff --git a/lib/ex_doc/formatter.ex b/lib/ex_doc/formatter.ex index 3c8b20b24..ff86934d3 100644 --- a/lib/ex_doc/formatter.ex +++ b/lib/ex_doc/formatter.ex @@ -137,10 +137,10 @@ defmodule ExDoc.Formatter do mod_id <> "." <> id end - defp autolink_and_render(doc, ".md", language, autolink_opts, _opts) do + defp autolink_and_render(doc, ".md", language, autolink_opts, opts) do doc |> language.autolink_doc(autolink_opts) - |> ExDoc.DocAST.to_markdown_string() + |> ExDoc.DocAST.highlight(language, opts) end defp autolink_and_render(doc, _html_ext, language, autolink_opts, opts) do diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 373473e40..f008076c3 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -39,6 +39,12 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do static_file |> Path.basename() |> text_to_id() end + def node_doc(%{doc: doc}) when is_list(doc) do + # Handle DocAST by converting to markdown + ExDoc.DocAST.to_markdown(doc) + end + + def node_doc(%{doc: doc}) when is_binary(doc), do: doc def node_doc(%{source_doc: %{"en" => source}}) when is_binary(source), do: source def node_doc(%{rendered_doc: source}) when is_binary(source), do: source From b4a4ba5004b1b221fb9769d252bce1aa28411381 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 12:37:06 -0400 Subject: [PATCH 04/33] refactor: simplify to_markdown function by removing post-processing argument and updating related calls --- lib/ex_doc/doc_ast.ex | 63 ++++++++++++-------------------- lib/ex_doc/formatter/markdown.ex | 52 +++++--------------------- 2 files changed, 33 insertions(+), 82 deletions(-) diff --git a/lib/ex_doc/doc_ast.ex b/lib/ex_doc/doc_ast.ex index bf8601044..7257599f6 100644 --- a/lib/ex_doc/doc_ast.ex +++ b/lib/ex_doc/doc_ast.ex @@ -67,81 +67,66 @@ defmodule ExDoc.DocAST do @doc """ Transform AST into markdown string. - - The optional `fun` argument allows post-processing each AST node - after it's been converted to markdown. """ - def to_markdown(ast, fun \\ fn _ast, string -> string end) + def to_markdown(ast) - def to_markdown(binary, _fun) when is_binary(binary) do + def to_markdown(binary) when is_binary(binary) do ExDoc.Utils.h(binary) end - def to_markdown(list, fun) when is_list(list) do - result = Enum.map_join(list, "", &to_markdown(&1, fun)) - fun.(list, result) + def to_markdown(list) when is_list(list) do + Enum.map_join(list, "", &to_markdown/1) end - def to_markdown({:comment, _attrs, inner, _meta} = ast, fun) do - fun.(ast, "") + def to_markdown({:comment, _attrs, inner, _meta}) do + "" end - def to_markdown({:code, attrs, inner, _meta} = ast, fun) do + def to_markdown({:code, attrs, inner, _meta}) do lang = attrs[:class] || "" - result = """ + """ ```#{lang} #{inner} ``` """ - - fun.(ast, result) end - def to_markdown({:a, attrs, inner, _meta} = ast, fun) do - result = "[#{to_markdown(inner, fun)}](#{attrs[:href]})" - fun.(ast, result) + def to_markdown({:a, attrs, inner, _meta}) do + "[#{to_markdown(inner)}](#{attrs[:href]})" end - def to_markdown({:hr, _attrs, _inner, _meta} = ast, fun) do - result = "\n\n---\n\n" - fun.(ast, result) + def to_markdown({:hr, _attrs, _inner, _meta}) do + "\n\n---\n\n" end - def to_markdown({:p, _attrs, inner, _meta} = ast, fun) do - result = to_markdown(inner, fun) <> "\n\n" - fun.(ast, result) + def to_markdown({:p, _attrs, inner, _meta}) do + to_markdown(inner) <> "\n\n" end - def to_markdown({:br, _attrs, _inner, _meta} = ast, fun) do - result = "\n\n" - fun.(ast, result) + def to_markdown({:br, _attrs, _inner, _meta}) do + "\n\n" end - def to_markdown({:img, attrs, _inner, _meta} = ast, fun) do + def to_markdown({:img, attrs, _inner, _meta}) do alt = attrs[:alt] || "" title = attrs[:title] || "" - result = "![#{alt}](#{attrs[:src]} \"#{title}\")" - fun.(ast, result) + "![#{alt}](#{attrs[:src]} \"#{title}\")" end # ignoring these: area base col command embed input keygen link meta param source track wbr - def to_markdown({tag, _attrs, _inner, _meta} = ast, fun) when tag in @void_elements do - result = "" - fun.(ast, result) + def to_markdown({tag, _attrs, _inner, _meta}) when tag in @void_elements do + "" end - def to_markdown({_tag, _attrs, inner, %{verbatim: true}} = ast, fun) do - result = Enum.join(inner, "") - fun.(ast, result) + def to_markdown({_tag, _attrs, inner, %{verbatim: true}}) do + Enum.join(inner, "") end - def to_markdown({_tag, _attrs, inner, _meta} = ast, fun) do - result = to_markdown(inner, fun) - fun.(ast, result) + def to_markdown({_tag, _attrs, inner, _meta}) do + to_markdown(inner) end - ## parse markdown defp parse_markdown(markdown, opts) do diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex index d4f3c7be3..ea0ef48ab 100644 --- a/lib/ex_doc/formatter/markdown.ex +++ b/lib/ex_doc/formatter/markdown.ex @@ -114,7 +114,7 @@ defmodule ExDoc.Formatter.MARKDOWN do modules_info = nodes_map.modules |> Enum.map(fn module_node -> - "- **#{module_node.title}** (#{module_node.id}.md): #{module_node.doc |> extract_summary()}" + "- **#{module_node.title}** (#{module_node.id}.md): #{module_node.doc |> ExDoc.DocAST.synopsis() |> extract_plain_text()}" end) |> Enum.join("\n") @@ -123,7 +123,7 @@ defmodule ExDoc.Formatter.MARKDOWN do tasks_list = nodes_map.tasks |> Enum.map(fn task_node -> - "- **#{task_node.title}** (#{task_node.id}.md): #{task_node.doc |> extract_summary()}" + "- **#{task_node.title}** (#{task_node.id}.md): #{task_node.doc |> ExDoc.DocAST.synopsis() |> extract_plain_text()}" end) |> Enum.join("\n") @@ -157,55 +157,21 @@ defmodule ExDoc.Formatter.MARKDOWN do project_info <> modules_info <> tasks_info <> extras_info end - defp extract_summary(nil), do: "No documentation available" - defp extract_summary(""), do: "No documentation available" - - defp extract_summary(doc) when is_binary(doc) do - doc - |> String.split("\n") - |> Enum.find("", fn line -> String.trim(line) != "" end) + defp extract_plain_text(html) when is_binary(html) do + html + |> String.replace(~r/<[^>]*>/, "") + |> String.replace(~r/\s+/, " ") |> String.trim() |> case do "" -> "No documentation available" - summary -> - summary + text -> + text |> String.slice(0, 150) |> then(fn s -> if String.length(s) == 150, do: s <> "...", else: s end) end end - defp extract_summary(doc_ast) when is_list(doc_ast) do - # For DocAST (which is a list), extract the first text node - extract_first_text_from_ast(doc_ast) - end - - defp extract_summary(_), do: "No documentation available" - - defp extract_first_text_from_ast([]), do: "No documentation available" - - defp extract_first_text_from_ast([{:p, _, content} | _rest]) do - extract_text_from_content(content) - |> String.slice(0, 150) - |> then(fn s -> if String.length(s) == 150, do: s <> "...", else: s end) - end - - defp extract_first_text_from_ast([_node | rest]) do - extract_first_text_from_ast(rest) - end - - defp extract_text_from_content([]), do: "" - defp extract_text_from_content([text | _rest]) when is_binary(text), do: text - - defp extract_text_from_content([{_tag, _attrs, content} | rest]) do - case extract_text_from_content(content) do - "" -> extract_text_from_content(rest) - text -> text - end - end - - defp extract_text_from_content([_node | rest]) do - extract_text_from_content(rest) - end + defp extract_plain_text(_), do: "No documentation available" end From 9770ce7bf526134ad989206647f14d1a9ddc8cf9 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 12:48:55 -0400 Subject: [PATCH 05/33] feat: implement node_synopsis function to extract and format documentation synopses for Markdown --- lib/ex_doc/formatter/markdown/templates.ex | 70 +++++++++++++++++++ .../markdown/templates/summary_template.eex | 4 +- 2 files changed, 72 insertions(+), 2 deletions(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index f008076c3..a557e9306 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -56,6 +56,57 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do def node_doc(_), do: nil + @doc """ + Get synopsis for a node, handling both DocAST and string documentation. + Uses DocAST synopsis extraction logic for consistency with HTML formatter. + """ + def node_synopsis(%{doc: doc}) when is_list(doc) do + # For DocAST, extract synopsis DocAST and convert to markdown + case extract_synopsis_ast(doc) do + nil -> nil + synopsis_ast -> ExDoc.DocAST.to_markdown(synopsis_ast) + end + end + + def node_synopsis(%{doc: doc}) when is_binary(doc) do + synopsis(doc) + end + + def node_synopsis(%{source_doc: %{"en" => source}}) when is_binary(source) do + synopsis(source) + end + + def node_synopsis(%{rendered_doc: source}) when is_binary(source) do + synopsis(source) + end + + def node_synopsis(%{source_doc: %{"en" => source}}) when is_list(source) do + # For Erlang DocAST, extract synopsis and convert to plain text + case extract_synopsis_ast(source) do + nil -> nil + synopsis_ast -> synopsis_ast |> ExDoc.DocAST.to_markdown() |> extract_plain_text() + end + end + + def node_synopsis(_), do: nil + + # Extract synopsis as DocAST (similar to ExDoc.DocAST.synopsis but returns AST instead of HTML string) + defp extract_synopsis_ast({:p, _attrs, [_ | _] = inner, _meta}) do + inner = + case Enum.split(inner, -1) do + {pre, [post]} when is_binary(post) -> + pre ++ [String.trim_trailing(post, ":")] + + _ -> + inner + end + + {:p, [], ExDoc.DocAST.remove_ids(inner), %{}} + end + + defp extract_synopsis_ast([head | _]), do: extract_synopsis_ast(head) + defp extract_synopsis_ast(_other), do: nil + defp extract_text_from_doc_ast(ast) when is_list(ast) do Enum.map_join(ast, "\n\n", &extract_text_from_doc_ast/1) end @@ -71,6 +122,25 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do defp extract_text_from_doc_ast(text) when is_binary(text), do: text defp extract_text_from_doc_ast(_), do: "" + # Extract plain text from markdown (similar to the one in markdown.ex but here for templates) + defp extract_plain_text(markdown) when is_binary(markdown) do + markdown + |> String.replace(~r/<[^>]*>/, "") + |> String.replace(~r/\s+/, " ") + |> String.trim() + |> case do + "" -> + nil + + text -> + text + |> String.slice(0, 150) + |> then(fn s -> if String.length(s) == 150, do: s <> "...", else: s end) + end + end + + defp extract_plain_text(_), do: nil + @doc """ Gets the first paragraph of the documentation of a node. It strips surrounding white-spaces and trailing `:`. diff --git a/lib/ex_doc/formatter/markdown/templates/summary_template.eex b/lib/ex_doc/formatter/markdown/templates/summary_template.eex index 7d8ffcb7b..a453248be 100644 --- a/lib/ex_doc/formatter/markdown/templates/summary_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/summary_template.eex @@ -8,8 +8,8 @@ > <%= h(deprecated) %> <% end %> -<%= if doc = node_doc(node) do %> -<%= synopsis(doc) %> +<%= if synopsis_content = node_synopsis(node) do %> +<%= synopsis_content %> <% end %> <% end %> From 97cdfa01c63e74c8360a98b0ebfbbd6308a243ba Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 13:34:44 -0400 Subject: [PATCH 06/33] style: update comments for clarity and improve code readability in doc_ast.ex and templates.ex --- lib/ex_doc/doc_ast.ex | 2 +- lib/ex_doc/formatter/markdown/templates.ex | 7 +++---- 2 files changed, 4 insertions(+), 5 deletions(-) diff --git a/lib/ex_doc/doc_ast.ex b/lib/ex_doc/doc_ast.ex index 7257599f6..f2f954104 100644 --- a/lib/ex_doc/doc_ast.ex +++ b/lib/ex_doc/doc_ast.ex @@ -114,7 +114,7 @@ defmodule ExDoc.DocAST do "![#{alt}](#{attrs[:src]} \"#{title}\")" end - # ignoring these: area base col command embed input keygen link meta param source track wbr + # Ignoring these: area base col command embed input keygen link meta param source track wbr def to_markdown({tag, _attrs, _inner, _meta}) when tag in @void_elements do "" end diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index a557e9306..338949ff2 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -21,9 +21,9 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do @doc """ Returns the formatted title for the module page. """ - def module_type(%{type: :task}), do: "" - def module_type(%{type: :module}), do: "" - def module_type(%{type: type}), do: "(#{type})" + def module_type(%{type: :task} = _node), do: "" + def module_type(%{type: :module} = _node), do: "" + def module_type(%{type: type} = _node), do: "(#{type})" @doc """ Format the attribute type used to define the spec of the given `node`. @@ -196,7 +196,6 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do @doc """ Creates the table of contents. - """ EEx.function_from_file( :def, From c1970a75b6b709ac4970df472c3076fd47182861 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 13:35:44 -0400 Subject: [PATCH 07/33] style: add period to documentation comments for consistency in EPUB and Markdown templates --- lib/ex_doc/formatter/epub/templates.ex | 2 +- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/ex_doc/formatter/epub/templates.ex b/lib/ex_doc/formatter/epub/templates.ex index 22dd483b8..94a232f48 100644 --- a/lib/ex_doc/formatter/epub/templates.ex +++ b/lib/ex_doc/formatter/epub/templates.ex @@ -20,7 +20,7 @@ defmodule ExDoc.Formatter.EPUB.Templates do end @doc """ - Generated ID for static file + Generated ID for static file. """ def static_file_to_id(static_file) do static_file |> Path.basename() |> text_to_id() diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 338949ff2..d21184d30 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -33,7 +33,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do end @doc """ - Generated ID for static file + Generated ID for static file. """ def static_file_to_id(static_file) do static_file |> Path.basename() |> text_to_id() From abe0e2638de0c31c9acae4a0b1fb89b72829e888 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Wed, 29 Oct 2025 13:36:53 -0400 Subject: [PATCH 08/33] style: add period to documentation comment for module_page function in EPUB templates --- lib/ex_doc/formatter/epub/templates.ex | 2 +- lib/ex_doc/formatter/html/templates.ex | 2 +- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/lib/ex_doc/formatter/epub/templates.ex b/lib/ex_doc/formatter/epub/templates.ex index 94a232f48..ceb3d269e 100644 --- a/lib/ex_doc/formatter/epub/templates.ex +++ b/lib/ex_doc/formatter/epub/templates.ex @@ -13,7 +13,7 @@ defmodule ExDoc.Formatter.EPUB.Templates do defp render_doc(ast), do: ast && ExDoc.DocAST.to_string(ast) @doc """ - Generate content from the module template for a given `node` + Generate content from the module template for a given `node`. """ def module_page(config, module_node) do module_template(config, module_node) diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex index 91c4ced07..ee7e9018a 100644 --- a/lib/ex_doc/formatter/html/templates.ex +++ b/lib/ex_doc/formatter/html/templates.ex @@ -13,7 +13,7 @@ defmodule ExDoc.Formatter.HTML.Templates do ] @doc """ - Generate content from the module template for a given `node` + Generate content from the module template for a given `node`. """ def module_page(module_node, config) do module_template(config, module_node) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index d21184d30..9e7207daf 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -7,7 +7,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do only: [before_closing_body_tag: 2, h: 1, text_to_id: 1] @doc """ - Generate content from the module template for a given `node` + Generate content from the module template for a given `node`. """ def module_page(config, module_node) do summary = From 68d0b022081de9c9bf80aa01f0199a1a5bbcd6a0 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 00:49:43 -0400 Subject: [PATCH 09/33] Update lib/ex_doc/formatter/markdown/templates/detail_template.eex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates/detail_template.eex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates/detail_template.eex b/lib/ex_doc/formatter/markdown/templates/detail_template.eex index 937bfe45a..b68ace209 100644 --- a/lib/ex_doc/formatter/markdown/templates/detail_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/detail_template.eex @@ -3,8 +3,8 @@ <%= if deprecated = node.deprecated do %> > This <%= node.type %> is deprecated. <%= h(deprecated) %>. -<% end %> +<% end %> <%= if node.specs != [] do %> <%= for spec <- node.specs do %> ```elixir From 2c69df3b940c69253fd93eb2bb863c609581996b Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 00:49:58 -0400 Subject: [PATCH 10/33] Update lib/ex_doc/formatter/markdown/templates/module_template.eex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates/module_template.eex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates/module_template.eex b/lib/ex_doc/formatter/markdown/templates/module_template.eex index c21285350..abc4f06b6 100644 --- a/lib/ex_doc/formatter/markdown/templates/module_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/module_template.eex @@ -4,8 +4,8 @@ <%= if deprecated = module.deprecated do %> > This <%= module.type %> is deprecated. <%=h deprecated %>. -<% end %> +<% end %> <%= if doc = node_doc(module) do %> <%= doc %> <% end %> From e21f6f34cd705083e4b3c4e7b32b1019dad09d3b Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 00:50:09 -0400 Subject: [PATCH 11/33] Update lib/ex_doc/formatter/markdown/templates/module_template.eex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates/module_template.eex | 1 - 1 file changed, 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates/module_template.eex b/lib/ex_doc/formatter/markdown/templates/module_template.eex index abc4f06b6..12c20ab57 100644 --- a/lib/ex_doc/formatter/markdown/templates/module_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/module_template.eex @@ -18,7 +18,6 @@ ## Contents <%= for {name, nodes} <- summary, _key = text_to_id(name) do %> - ### <%=h to_string(name) %> <%= for node <- nodes do %> From daf8d8d5bc4542d069ebc73375ebe8b770c9b066 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 00:50:18 -0400 Subject: [PATCH 12/33] Update lib/ex_doc/formatter/markdown/templates/summary_template.eex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates/summary_template.eex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates/summary_template.eex b/lib/ex_doc/formatter/markdown/templates/summary_template.eex index a453248be..05d0aeba7 100644 --- a/lib/ex_doc/formatter/markdown/templates/summary_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/summary_template.eex @@ -6,8 +6,8 @@ <%= if deprecated = node.deprecated do %> > <%= h(deprecated) %> -<% end %> +<% end %> <%= if synopsis_content = node_synopsis(node) do %> <%= synopsis_content %> <% end %> From fb2cb64a9d432f8d5c2646d76d960aaba75c0ef7 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 00:50:29 -0400 Subject: [PATCH 13/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 9e7207daf..baa90c948 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -90,7 +90,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do def node_synopsis(_), do: nil - # Extract synopsis as DocAST (similar to ExDoc.DocAST.synopsis but returns AST instead of HTML string) + # Extract synopsis as DocAST (similar to ExDoc.DocAST.synopsis but returns an AST instead of an HTML string). defp extract_synopsis_ast({:p, _attrs, [_ | _] = inner, _meta}) do inner = case Enum.split(inner, -1) do From 06cf6856ffe8da934d0434a75f617ff16d353014 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:00:58 -0400 Subject: [PATCH 14/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index baa90c948..d289ee416 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -26,7 +26,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do def module_type(%{type: type} = _node), do: "(#{type})" @doc """ - Format the attribute type used to define the spec of the given `node`. + Formats the attribute type used to define the spec of the given `node`. """ def format_spec_attribute(module, node) do module.language.format_spec_attribute(node) From 4180268ffb1b2b4aa7494a6941230a11d470c746 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:01:23 -0400 Subject: [PATCH 15/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index d289ee416..d343a2dd1 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -33,7 +33,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do end @doc """ - Generated ID for static file. + Generates an ID for a static file. """ def static_file_to_id(static_file) do static_file |> Path.basename() |> text_to_id() From 71bf9588bb807ea89d327bdac899f8d38b706503 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:01:46 -0400 Subject: [PATCH 16/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index d343a2dd1..57b3bbcf8 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -49,8 +49,8 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do def node_doc(%{rendered_doc: source}) when is_binary(source), do: source def node_doc(%{source_doc: %{"en" => source}}) when is_list(source) do - # Handle DocAST by converting to markdown - # For Erlang docs, we can extract text content + # Handle DocAST by converting to Markdown. + # For Erlang docs, we can extract the text content. extract_text_from_doc_ast(source) end From 8bd943052ac8367313f12095f9c1ae7252820f38 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:01:57 -0400 Subject: [PATCH 17/33] Update test/ex_doc/formatter/markdown_test.exs Co-authored-by: Eksperimental --- test/ex_doc/formatter/markdown_test.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/ex_doc/formatter/markdown_test.exs b/test/ex_doc/formatter/markdown_test.exs index 135f466ac..403162456 100644 --- a/test/ex_doc/formatter/markdown_test.exs +++ b/test/ex_doc/formatter/markdown_test.exs @@ -52,7 +52,7 @@ defmodule ExDoc.Formatter.MARKDOWNTest do generate_docs(doc_config(context)) content = File.read!(tmp_dir <> "/markdown/index.md") - assert content =~ ~r{^# Elixir v1\.0\.1 - Documentation - Table of contents$}m + assert content =~ ~r{^# Elixir v1\.0\.1 - Documentation - Table of Contents$}m assert content =~ ~r{## Modules} assert content =~ ~r{- \[CompiledWithDocs\]\(CompiledWithDocs\.md\)} assert content =~ ~r{- \[CompiledWithDocs\.Nested\]\(CompiledWithDocs\.Nested\.md\)} From 7e5d02b6801ceb4bf9ac399158ca4248ee1d28b3 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:02:06 -0400 Subject: [PATCH 18/33] Update lib/ex_doc/formatter/markdown/templates/nav_template.eex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates/nav_template.eex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates/nav_template.eex b/lib/ex_doc/formatter/markdown/templates/nav_template.eex index 48f11c99a..55434a410 100644 --- a/lib/ex_doc/formatter/markdown/templates/nav_template.eex +++ b/lib/ex_doc/formatter/markdown/templates/nav_template.eex @@ -1,4 +1,4 @@ -# <%= config.project %> v<%= config.version %> - Documentation - Table of contents +# <%= config.project %> v<%= config.version %> - Documentation - Table of Contents <%= nav_grouped_item_template config.extras %> <%= unless Enum.empty?(nodes.modules) do %> From 431d6ad4379859510faaa3eae70507ba2fed7db9 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:02:21 -0400 Subject: [PATCH 19/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 57b3bbcf8..47b583009 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -158,9 +158,8 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do def synopsis(_), do: nil - @heading_regex ~r/^(\#{1,6})\s+(.*)/m defp rewrite_headings(content) when is_binary(content) do - @heading_regex + ~r/^(\#{1,6})\s+(.*)/m |> Regex.scan(content) |> Enum.reduce(content, fn [match, level, title], content -> replacement = rewrite_heading(level, title) From 066af422c235284575a3d84760cdcaf299bb8c88 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:02:31 -0400 Subject: [PATCH 20/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 47b583009..af8b5671c 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -151,7 +151,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do @spec synopsis(nil) :: nil def synopsis(doc) when is_binary(doc) do case :binary.split(doc, "\n\n") do - [left, _] -> String.trim_trailing(left, ": ") <> "\n\n" + [left, _] -> String.trim_trailing(left) |> String.trim_trailing(left, ":") <> "\n\n" [all] -> all end end From 76f722896eb97c6f48ab360e9cd95cada95c4667 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:02:46 -0400 Subject: [PATCH 21/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index af8b5671c..15818155d 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -40,7 +40,7 @@ defmodule ExDoc.Formatter.MARKDOWN.Templates do end def node_doc(%{doc: doc}) when is_list(doc) do - # Handle DocAST by converting to markdown + # Handle DocAST by converting to Markdown. ExDoc.DocAST.to_markdown(doc) end From bdf6826e0e7ed19e6e0457a147545cd475cb5b70 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:03:33 -0400 Subject: [PATCH 22/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 15818155d..b388cb25d 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -1,4 +1,4 @@ -defmodule ExDoc.Formatter.MARKDOWN.Templates do +defmodule ExDoc.Formatter.Markdown.Templates do @moduledoc false require EEx From 6bcdbf4e8c613f5ef56a293b02705c1708acf893 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:03:58 -0400 Subject: [PATCH 23/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 1 - 1 file changed, 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index b388cb25d..e0e543dd5 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -58,7 +58,6 @@ defmodule ExDoc.Formatter.Markdown.Templates do @doc """ Get synopsis for a node, handling both DocAST and string documentation. - Uses DocAST synopsis extraction logic for consistency with HTML formatter. """ def node_synopsis(%{doc: doc}) when is_list(doc) do # For DocAST, extract synopsis DocAST and convert to markdown From 9906ad5e3cbffdeeb2ea52644b03fcd2f5086c04 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:04:10 -0400 Subject: [PATCH 24/33] Update lib/ex_doc/formatter/markdown.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex index ea0ef48ab..07dee87b0 100644 --- a/lib/ex_doc/formatter/markdown.ex +++ b/lib/ex_doc/formatter/markdown.ex @@ -1,4 +1,4 @@ -defmodule ExDoc.Formatter.MARKDOWN do +defmodule ExDoc.Formatter.Markdown do @moduledoc false alias __MODULE__.{Templates} From 4059a8d7b05852adbb5b34032389bdbc87a9099b Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:04:25 -0400 Subject: [PATCH 25/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index e0e543dd5..c50b735f7 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -60,7 +60,7 @@ defmodule ExDoc.Formatter.Markdown.Templates do Get synopsis for a node, handling both DocAST and string documentation. """ def node_synopsis(%{doc: doc}) when is_list(doc) do - # For DocAST, extract synopsis DocAST and convert to markdown + # For DocAST, extract synopsis DocAST and convert to Markdown. case extract_synopsis_ast(doc) do nil -> nil synopsis_ast -> ExDoc.DocAST.to_markdown(synopsis_ast) From 5f451e28551fd7ac7358357f5f4bfce38153ed64 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:04:39 -0400 Subject: [PATCH 26/33] Update lib/ex_doc/formatter/markdown/templates.ex Co-authored-by: Eksperimental --- lib/ex_doc/formatter/markdown/templates.ex | 1 - 1 file changed, 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index c50b735f7..1d4f292aa 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -80,7 +80,6 @@ defmodule ExDoc.Formatter.Markdown.Templates do end def node_synopsis(%{source_doc: %{"en" => source}}) when is_list(source) do - # For Erlang DocAST, extract synopsis and convert to plain text case extract_synopsis_ast(source) do nil -> nil synopsis_ast -> synopsis_ast |> ExDoc.DocAST.to_markdown() |> extract_plain_text() From 0e8111ba5607b7398adf160c4aecac75ef3ee318 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:05:24 -0400 Subject: [PATCH 27/33] Update lib/ex_doc/doc_ast.ex Co-authored-by: Eksperimental --- lib/ex_doc/doc_ast.ex | 1 - 1 file changed, 1 deletion(-) diff --git a/lib/ex_doc/doc_ast.ex b/lib/ex_doc/doc_ast.ex index f2f954104..2d9d9976f 100644 --- a/lib/ex_doc/doc_ast.ex +++ b/lib/ex_doc/doc_ast.ex @@ -114,7 +114,6 @@ defmodule ExDoc.DocAST do "![#{alt}](#{attrs[:src]} \"#{title}\")" end - # Ignoring these: area base col command embed input keygen link meta param source track wbr def to_markdown({tag, _attrs, _inner, _meta}) when tag in @void_elements do "" end From c9ab715c74d3da54913668a1b8f8280227fc6d96 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:05:39 -0400 Subject: [PATCH 28/33] Update test/ex_doc/formatter/markdown_test.exs Co-authored-by: Eksperimental --- test/ex_doc/formatter/markdown_test.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/ex_doc/formatter/markdown_test.exs b/test/ex_doc/formatter/markdown_test.exs index 403162456..a4546c78f 100644 --- a/test/ex_doc/formatter/markdown_test.exs +++ b/test/ex_doc/formatter/markdown_test.exs @@ -1,4 +1,4 @@ -defmodule ExDoc.Formatter.MARKDOWNTest do +defmodule ExDoc.Formatter.MarkdownTest do use ExUnit.Case, async: false @moduletag :tmp_dir From 6cdb64364bae9f6182511b093a59cd18fac8002e Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:05:52 -0400 Subject: [PATCH 29/33] Update test/ex_doc/formatter/markdown_test.exs Co-authored-by: Eksperimental --- test/ex_doc/formatter/markdown_test.exs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/ex_doc/formatter/markdown_test.exs b/test/ex_doc/formatter/markdown_test.exs index a4546c78f..6f054372f 100644 --- a/test/ex_doc/formatter/markdown_test.exs +++ b/test/ex_doc/formatter/markdown_test.exs @@ -22,7 +22,7 @@ defmodule ExDoc.Formatter.MarkdownTest do ExDoc.generate_docs(config[:project], config[:version], config) end - test "generates markdown files in the default directory", %{tmp_dir: tmp_dir} = context do + test "generates Markdown files in the default directory", %{tmp_dir: tmp_dir} = context do generate_docs(doc_config(context)) assert File.regular?(tmp_dir <> "/markdown/index.md") assert File.regular?(tmp_dir <> "/markdown/CompiledWithDocs.md") From f71c480a4fcfa6725cf04722b365497c88a959cd Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:08:50 -0400 Subject: [PATCH 30/33] Refactor normalize_output function in markdown formatter to use regex for line ending replacement --- lib/ex_doc/formatter/markdown.ex | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex index 07dee87b0..8a2f496c6 100644 --- a/lib/ex_doc/formatter/markdown.ex +++ b/lib/ex_doc/formatter/markdown.ex @@ -49,7 +49,7 @@ defmodule ExDoc.Formatter.Markdown do defp normalize_output(output) do output - |> String.replace(["\r\n", "\n"], "\n") + |> String.replace(~r/\r\n?/, "\n") |> String.replace(~r/\n{3,}/, "\n\n") end From 512fac12dab68fa42c3f2169e1f950c00a8cc146 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:11:53 -0400 Subject: [PATCH 31/33] Refactor formatter module name handling and improve markdown template spec attribute formatting --- lib/ex_doc.ex | 7 ++++++- lib/ex_doc/formatter/markdown/templates.ex | 4 ++-- 2 files changed, 8 insertions(+), 3 deletions(-) diff --git a/lib/ex_doc.ex b/lib/ex_doc.ex index c108c3560..6951660ed 100644 --- a/lib/ex_doc.ex +++ b/lib/ex_doc.ex @@ -35,11 +35,16 @@ defmodule ExDoc do end defp find_formatter(name) do - [ExDoc.Formatter, String.upcase(name)] + [ExDoc.Formatter, format_module_name(name)] |> Module.concat() |> check_formatter_module(name) end + defp format_module_name("html"), do: "HTML" + defp format_module_name("epub"), do: "EPUB" + defp format_module_name("markdown"), do: "Markdown" + defp format_module_name(name), do: String.upcase(name) + defp check_formatter_module(modname, argname) do if Code.ensure_loaded?(modname) do modname diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex index 1d4f292aa..ee835608b 100644 --- a/lib/ex_doc/formatter/markdown/templates.ex +++ b/lib/ex_doc/formatter/markdown/templates.ex @@ -26,7 +26,7 @@ defmodule ExDoc.Formatter.Markdown.Templates do def module_type(%{type: type} = _node), do: "(#{type})" @doc """ - Formats the attribute type used to define the spec of the given `node`. + Formats the attribute type used to define the spec of the given `node`. """ def format_spec_attribute(module, node) do module.language.format_spec_attribute(node) @@ -149,7 +149,7 @@ defmodule ExDoc.Formatter.Markdown.Templates do @spec synopsis(nil) :: nil def synopsis(doc) when is_binary(doc) do case :binary.split(doc, "\n\n") do - [left, _] -> String.trim_trailing(left) |> String.trim_trailing(left, ":") <> "\n\n" + [left, _] -> (String.trim_trailing(left) |> String.trim_trailing(":")) <> "\n\n" [all] -> all end end From 2994e6c91f54a351d29c7b8dff613cfd5907e8a6 Mon Sep 17 00:00:00 2001 From: Yordis Prieto Date: Fri, 31 Oct 2025 01:49:08 -0400 Subject: [PATCH 32/33] Add tests for DocAST.to_markdown/1 functionality --- test/ex_doc/doc_ast_test.exs | 179 +++++++++++++++- test/ex_doc/formatter/markdown_test.exs | 271 ++++++++++++++++++++++++ 2 files changed, 444 insertions(+), 6 deletions(-) diff --git a/test/ex_doc/doc_ast_test.exs b/test/ex_doc/doc_ast_test.exs index abbf54d0c..b55224ce6 100644 --- a/test/ex_doc/doc_ast_test.exs +++ b/test/ex_doc/doc_ast_test.exs @@ -47,6 +47,179 @@ defmodule ExDoc.DocASTTest do end end + describe "to_markdown/1" do + test "converts simple text" do + assert DocAST.to_markdown("hello world") == "hello world" + end + + test "escapes HTML entities in text" do + assert DocAST.to_markdown("") == + "<script>alert('xss')</script>" + + assert DocAST.to_markdown("Tom & Jerry") == "Tom & Jerry" + end + + test "converts lists of elements" do + ast = ["Hello ", "world", "!"] + assert DocAST.to_markdown(ast) == "Hello world!" + end + + test "converts paragraphs" do + ast = {:p, [], ["Hello world"], %{}} + assert DocAST.to_markdown(ast) == "Hello world\n\n" + end + + test "converts multiple paragraphs" do + ast = [ + {:p, [], ["First paragraph"], %{}}, + {:p, [], ["Second paragraph"], %{}} + ] + + assert DocAST.to_markdown(ast) == "First paragraph\n\nSecond paragraph\n\n" + end + + test "converts code blocks with language" do + ast = {:code, [class: "elixir"], "defmodule Test do\n def hello, do: :world\nend", %{}} + expected = "```elixir\ndefmodule Test do\n def hello, do: :world\nend\n```\n" + assert DocAST.to_markdown(ast) == expected + end + + test "converts code blocks without language" do + ast = {:code, [], "some code", %{}} + assert DocAST.to_markdown(ast) == "```\nsome code\n```\n" + end + + test "converts inline code with class attribute" do + ast = {:code, [class: "language-elixir"], "IO.puts", %{}} + expected = "```language-elixir\nIO.puts\n```\n" + assert DocAST.to_markdown(ast) == expected + end + + test "converts links" do + ast = {:a, [href: "https://example.com"], ["Example"], %{}} + assert DocAST.to_markdown(ast) == "[Example](https://example.com)" + end + + test "converts links with nested content" do + ast = {:a, [href: "/docs"], [{:code, [], ["API"], %{}}], %{}} + assert DocAST.to_markdown(ast) == "[```\nAPI\n```\n](/docs)" + end + + test "converts images with alt and title" do + ast = {:img, [src: "image.png", alt: "Alt text", title: "Title"], [], %{}} + assert DocAST.to_markdown(ast) == "![Alt text](image.png \"Title\")" + end + + test "converts images with missing attributes" do + ast = {:img, [src: "image.png"], [], %{}} + assert DocAST.to_markdown(ast) == "![](image.png \"\")" + end + + test "converts horizontal rules" do + ast = {:hr, [], [], %{}} + assert DocAST.to_markdown(ast) == "\n\n---\n\n" + end + + test "converts line breaks" do + ast = {:br, [], [], %{}} + assert DocAST.to_markdown(ast) == "\n\n" + end + + test "converts comments" do + ast = {:comment, [], [" This is a comment "], %{}} + assert DocAST.to_markdown(ast) == "" + end + + test "handles void elements" do + void_elements = [ + :area, + :base, + :col, + :embed, + :input, + :link, + :meta, + :param, + :source, + :track, + :wbr + ] + + for element <- void_elements do + ast = {element, [], [], %{}} + assert DocAST.to_markdown(ast) == "" + end + end + + test "handles verbatim content" do + ast = {:pre, [], [" verbatim \n content "], %{verbatim: true}} + assert DocAST.to_markdown(ast) == " verbatim \n content " + end + + test "converts nested structures" do + ast = {:p, [], ["Hello ", {:strong, [], ["world"], %{}}, "!"], %{}} + + result = DocAST.to_markdown(ast) + assert result =~ "Hello" + assert result =~ "world" + assert result =~ "!" + assert String.ends_with?(result, "\n\n") + end + + test "handles unknown elements by extracting content" do + ast = {:custom_element, [class: "special"], ["Content"], %{}} + assert DocAST.to_markdown(ast) == "Content" + end + + test "handles complex nested document" do + ast = [ + {:h1, [], ["Main Title"], %{}}, + {:p, [], ["Introduction paragraph with ", {:a, [href: "/link"], ["a link"], %{}}], %{}}, + {:code, [class: "elixir"], "IO.puts \"Hello\"", %{}}, + {:hr, [], [], %{}}, + {:p, [], ["Final paragraph"], %{}} + ] + + result = DocAST.to_markdown(ast) + + assert result =~ "Main Title" + assert result =~ "Introduction paragraph with [a link](/link)" + assert result =~ "```elixir\nIO.puts \"Hello\"\n```\n" + assert result =~ "\n\n---\n\n" + assert result =~ "Final paragraph\n\n" + end + + test "handles empty content gracefully" do + assert DocAST.to_markdown([]) == "" + assert DocAST.to_markdown({:p, [], [], %{}}) == "\n\n" + end + + test "preserves whitespace in code blocks" do + code_content = " def hello do\n :world\n end" + ast = {:code, [class: "elixir"], code_content, %{}} + result = DocAST.to_markdown(ast) + + assert result =~ "```elixir" + assert String.contains?(result, code_content) + assert result =~ "```" + end + + test "handles mixed content types" do + ast = [ + "Plain text", + {:p, [], ["Paragraph text"], %{}}, + {:code, [], "code", %{}}, + "More plain text" + ] + + result = DocAST.to_markdown(ast) + assert result =~ "Plain text" + assert result =~ "Paragraph text\n\n" + assert result =~ "```\ncode\n```\n" + assert result =~ "More plain text" + end + end + describe "to_string/2" do test "simple" do markdown = """ @@ -161,13 +334,11 @@ defmodule ExDoc.DocASTTest do describe "highlight" do test "with default class" do - # Four spaces assert highlight(""" mix run --no-halt path/to/file.exs """) =~ ~r{
.*}
 
-      # Code block without language
       assert highlight("""
              ```
              mix run --no-halt path/to/file.exs
@@ -175,7 +346,6 @@ defmodule ExDoc.DocASTTest do """) =~ ~r{
.*}
 
-      # Pre IAL
       assert highlight("""
              ```
              mix run --no-halt path/to/file.exs
@@ -184,7 +354,6 @@ defmodule ExDoc.DocASTTest do """) =~ ~r{
.*}
 
-      # Code with language
       assert highlight("""
              ```html
              
@@ -192,7 +361,6 @@ defmodule ExDoc.DocASTTest do
              """) =~
                ~r{
.*}
 
-      # Code with shell detection
       assert highlight("""
              ```
              $ hello
@@ -200,7 +368,6 @@ defmodule ExDoc.DocASTTest do
              """) =~
                ~r{
\$.*}
 
-      # Nested in another element
       assert highlight("""
              > ```elixir
              > hello
diff --git a/test/ex_doc/formatter/markdown_test.exs b/test/ex_doc/formatter/markdown_test.exs
index 6f054372f..0918baafa 100644
--- a/test/ex_doc/formatter/markdown_test.exs
+++ b/test/ex_doc/formatter/markdown_test.exs
@@ -130,4 +130,275 @@ defmodule ExDoc.Formatter.MarkdownTest do
     assert content =~ ~r{## Modules}
     assert content =~ ~r{- \*\*CompiledWithDocs\*\* \(CompiledWithDocs\.md\):}
   end
+
+  describe "markdown output validation" do
+    test "generates proper markdown syntax", %{tmp_dir: tmp_dir} = context do
+      generate_docs(doc_config(context))
+      content = File.read!(tmp_dir <> "/markdown/CompiledWithDocs.md")
+
+      assert content =~ ~r/^# CompiledWithDocs/m
+      assert content =~ ~r/^## Table of Contents/m
+      assert content =~ ~r/^### Functions/m
+      assert content =~ ~r/^#### `/m
+      assert content =~ ~r/```makeup elixir/s
+      assert content =~ ~r/\[.*\]\(#.*\)/ || content =~ ~r/\[.*\]\(http.*\)/
+      refute content =~ ~r/^# .*\n^# /m
+    end
+
+    test "handles complex documentation elements", %{tmp_dir: tmp_dir} = context do
+      generate_docs(doc_config(context))
+      content = File.read!(tmp_dir <> "/markdown/CompiledWithDocs.md")
+
+      assert content =~ ~r/#### `example\(foo, bar.*\)`/
+      assert content =~ ~r/> This function is deprecated\./
+      assert content =~ ~r/<\/a>/
+    end
+
+    test "generates valid navigation structure", %{tmp_dir: tmp_dir} = context do
+      generate_docs(doc_config(context))
+      content = File.read!(tmp_dir <> "/markdown/index.md")
+
+      assert content =~ ~r/^# Elixir v1\.0\.1 - Documentation - Table of Contents$/m
+      assert content =~ ~r/- \[CompiledWithDocs\]\(CompiledWithDocs\.md\)/
+      assert content =~ ~r/- \[CompiledWithDocs\.Nested\]\(CompiledWithDocs\.Nested\.md\)/
+      assert content =~ ~r/- \[mix task_with_docs\]\(Mix\.Tasks\.TaskWithDocs\.md\)/
+      refute content =~ ~r/\]\([^)]*\s[^)]*\)/
+      refute content =~ ~r/\[[^\]]*\]\(\)/
+    end
+
+    test "generates proper markdown escaping", %{tmp_dir: tmp_dir} = context do
+      generate_docs(doc_config(context))
+      content = File.read!(tmp_dir <> "/markdown/CompiledWithDocs.md")
+
+      assert content =~ ~r/<|>|&/ || !String.contains?(content, "