This <%= module.type %> is deprecated. <%= h(deprecated) %>.
diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex
new file mode 100644
index 000000000..3535f2804
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown.ex
@@ -0,0 +1,227 @@
+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
+ # Legacy implementation - build extras inline
+ extras = Formatter.build_extras(config, ".md")
+ run_with_extras(project_nodes, filtered_modules, extras, config)
+ end
+
+ @doc """
+ Generates Markdown documentation using pre-built ExtraNode structures.
+
+ This is the new architecture that accepts pre-processed extras to eliminate
+ duplicate work when multiple formatters are used.
+ """
+ @spec run_with_extra_nodes([ExDoc.ModuleNode.t()], [ExDoc.ModuleNode.t()], [ExDoc.ExtraNode.t()], ExDoc.Config.t()) :: String.t()
+ def run_with_extra_nodes(project_nodes, filtered_modules, extra_nodes, config) when is_map(config) do
+ # Convert ExtraNode structures to the format expected by Markdown formatter
+ extras = extra_nodes_to_markdown_extras(extra_nodes)
+ run_with_extras(project_nodes, filtered_modules, extras, config)
+ end
+
+ # Convert ExtraNode structures to the format expected by Markdown formatter
+ defp extra_nodes_to_markdown_extras(extra_nodes) do
+ extra_nodes
+ |> Enum.map(fn %ExDoc.ExtraNode{} = node ->
+ # Note: Markdown formatter's generate_extras expects 'source' to contain processed markdown content
+ processed_content = ExDoc.ExtraNode.content_for_format(node, :markdown)
+ %{
+ source: processed_content, # This is what gets written to .md files
+ content: processed_content,
+ group: node.group,
+ id: node.id,
+ source_path: node.source_path,
+ source_url: node.source_url,
+ title: node.title,
+ title_content: node.title_content
+ }
+ end)
+ |> Enum.chunk_by(& &1.group)
+ |> Enum.map(&{hd(&1).group, &1})
+ end
+
+ # Common implementation used by both legacy and new architecture
+ defp run_with_extras(project_nodes, filtered_modules, extras, config) do
+ Utils.unset_warned()
+
+ config = normalize_config(config)
+ File.rm_rf!(config.output)
+ File.mkdir_p!(config.output)
+
+ 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} -> extras end)
+ |> Enum.map(fn extra ->
+ "- **#{extra.title}** (#{extra.id}.md): #{extra.title}"
+ end)
+ |> Enum.join("\n")
+
+ "\n\n## Guides\n\n" <> extras_list
+ 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..8b7cd8222
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates.ex
@@ -0,0 +1,155 @@
+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]
+
+ alias ExDoc.Formatter.HTML.Templates, as: H
+
+ @doc """
+ Generate content from the module template for a given `node`
+ """
+ def module_page(config, module_node) do
+ summary = H.module_summary(module_node)
+ 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 """
+ 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..1842c66d0
--- /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
+<%= H.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/lib/ex_doc/language/elixir.ex b/lib/ex_doc/language/elixir.ex
index 3fc826389..2a2ee56ce 100644
--- a/lib/ex_doc/language/elixir.ex
+++ b/lib/ex_doc/language/elixir.ex
@@ -654,6 +654,14 @@ defmodule ExDoc.Language.Elixir do
defp typespec_name({:"::", _, [{name, _, _}, _]}), do: Atom.to_string(name)
defp typespec_name({:when, _, [left, _]}), do: typespec_name(left)
defp typespec_name({name, _, _}) when is_atom(name), do: Atom.to_string(name)
+ # Handle case where spec is already a string (possibly pre-processed)
+ defp typespec_name(spec) when is_binary(spec) do
+ # Extract the function name from the beginning of the spec string
+ case Regex.run(~r/^([a-zA-Z_][a-zA-Z0-9_]*[?!]?)/, spec) do
+ [_, name] -> name
+ _ -> "unknown"
+ end
+ end
# extract out function name so we don't process it. This is to avoid linking it when there's
# a type with the same name
@@ -699,7 +707,11 @@ defmodule ExDoc.Language.Elixir do
end
if url do
- ~s[
#{ExDoc.Utils.h(call_string)}]
+ if config.ext == ".md" do
+ ~s[\[#{ExDoc.Utils.h(call_string)}\](#{url})]
+ else
+ ~s[
#{ExDoc.Utils.h(call_string)}]
+ end
else
call_string
end <> do_typespec(rest, config)
diff --git a/lib/ex_doc/language/erlang.ex b/lib/ex_doc/language/erlang.ex
index 6b6e7edad..46b64eb92 100644
--- a/lib/ex_doc/language/erlang.ex
+++ b/lib/ex_doc/language/erlang.ex
@@ -224,6 +224,16 @@ defmodule ExDoc.Language.Erlang do
def autolink_spec(ast, opts) do
config = struct!(Autolink, opts)
+ # Handle case where spec is already a string (possibly pre-processed)
+ case ast do
+ spec when is_binary(spec) ->
+ spec # Return the spec as-is if it's already processed
+ _ ->
+ autolink_spec_ast(ast, config)
+ end
+ end
+
+ defp autolink_spec_ast(ast, config) do
{name, anno, quoted} =
case ast do
{:attribute, anno, kind, {mfa, ast}} when kind in [:spec, :callback] ->
@@ -695,7 +705,11 @@ defmodule ExDoc.Language.Erlang do
end
if url do
- ~s|
#{string}(|
+ if config.ext == ".md" do
+ ~s|[#{string}\](#{url})(|
+ else
+ ~s|
#{string}(|
+ end
else
string <> "("
end
diff --git a/lib/mix/tasks/docs.ex b/lib/mix/tasks/docs.ex
index 35ca940b9..2c8df232d 100644
--- a/lib/mix/tasks/docs.ex
+++ b/lib/mix/tasks/docs.ex
@@ -12,9 +12,9 @@ defmodule Mix.Tasks.Docs do
* `--canonical`, `-n` - Indicate the preferred URL with
`rel="canonical"` link element, defaults to no canonical path
- * `--formatter`, `-f` - Which formatters to use, `html` or
- `epub`. This option can be given more than once. By default,
- both `html` and `epub` are generated.
+ * `--formatter`, `-f` - Which formatters to use, `html`,
+ `epub`, or `markdown`. This option can be given more than once. By default,
+ `html`, `epub`, and `markdown` are generated.
* `--language` - Specifies the language to annotate the
EPUB output in valid [BCP 47](https://tools.ietf.org/html/bcp47)
@@ -130,7 +130,7 @@ defmodule Mix.Tasks.Docs do
against the complete module name (which includes the "Elixir." prefix for
Elixir modules). If a module has `@moduledoc false`, then it is always excluded.
- * `:formatters` - Formatter to use; default: ["html", "epub"], options: "html", "epub".
+ * `:formatters` - Formatter to use; default: ["html", "epub", "markdown"], options: "html", "epub", "markdown".
* `:groups_for_extras`, `:groups_for_modules`, `:groups_for_docs`, and `:default_group_for_doc` -
See the "Groups" section
@@ -622,7 +622,7 @@ defmodule Mix.Tasks.Docs do
defp normalize_formatters(options) do
formatters =
case Keyword.get_values(options, :formatter) do
- [] -> options[:formatters] || ["html", "epub"]
+ [] -> options[:formatters] || ["html", "epub", "markdown"]
values -> values
end
diff --git a/test/ex_doc/cli_test.exs b/test/ex_doc/cli_test.exs
index 72dfb28d2..84cabe2e4 100644
--- a/test/ex_doc/cli_test.exs
+++ b/test/ex_doc/cli_test.exs
@@ -10,13 +10,13 @@ defmodule ExDoc.CLITest do
end
test "minimum command-line options" do
- {[html, epub], _io} = run(["ExDoc", "1.2.3", @ebin])
+ {[html, epub, markdown], _io} = run(["ExDoc", "1.2.3", @ebin])
assert html ==
{"ExDoc", "1.2.3",
[
formatter: "html",
- formatters: ["html", "epub"],
+ formatters: ["html", "epub", "markdown"],
apps: [:ex_doc],
source_beam: [@ebin]
]}
@@ -25,7 +25,16 @@ defmodule ExDoc.CLITest do
{"ExDoc", "1.2.3",
[
formatter: "epub",
- formatters: ["html", "epub"],
+ formatters: ["html", "epub", "markdown"],
+ apps: [:ex_doc],
+ source_beam: @ebin
+ ]}
+
+ assert markdown ==
+ {"ExDoc", "1.2.3",
+ [
+ formatter: "markdown",
+ formatters: ["html", "epub", "markdown"],
apps: [:ex_doc],
source_beam: [@ebin]
]}
diff --git a/test/ex_doc/formatter/html_test.exs b/test/ex_doc/formatter/html_test.exs
index 0f3e7b05c..ab9727f68 100644
--- a/test/ex_doc/formatter/html_test.exs
+++ b/test/ex_doc/formatter/html_test.exs
@@ -17,12 +17,22 @@ defmodule ExDoc.Formatter.HTMLTest do
@before_closing_footer_tag_content_html "UNIQUE:
©BEFORE-CLOSING-FOOTER-TAG-EPUB"
defp before_closing_head_tag(:html), do: @before_closing_head_tag_content_html
+ defp before_closing_head_tag(:markdown), do: ""
+
defp before_closing_body_tag(:html), do: @before_closing_body_tag_content_html
+ defp before_closing_body_tag(:markdown), do: ""
+
defp before_closing_footer_tag(:html), do: @before_closing_footer_tag_content_html
+ defp before_closing_footer_tag(:markdown), do: ""
def before_closing_head_tag(:html, name), do: "
"
+ def before_closing_head_tag(:markdown, name), do: ""
+
def before_closing_body_tag(:html, name), do: "
#{name}
"
+ def before_closing_body_tag(:markdown, name), do: ""
+
def before_closing_footer_tag(:html, name), do: "
#{name}
"
+ def before_closing_footer_tag(:markdown, name), do: ""
defp doc_config(%{tmp_dir: tmp_dir} = _context) do
[
@@ -1036,4 +1046,16 @@ defmodule ExDoc.Formatter.HTMLTest do
after
File.rm_rf!("test/tmp/html_assets")
end
+
+ test "generates llms.txt index file", %{tmp_dir: tmp_dir} = context do
+ generate_docs(doc_config(context))
+
+ assert File.regular?(tmp_dir <> "/html/llms.txt")
+ content = File.read!(tmp_dir <> "/html/llms.txt")
+
+ assert content =~ "# Elixir 1.0.1"
+ assert content =~ "documentation index for Large Language Models"
+ assert content =~ "## Modules"
+ assert content =~ "**CompiledWithDocs** (CompiledWithDocs.html):"
+ end
end
diff --git a/test/ex_doc/formatter/markdown/templates_test.exs b/test/ex_doc/formatter/markdown/templates_test.exs
new file mode 100644
index 000000000..0a442ed4e
--- /dev/null
+++ b/test/ex_doc/formatter/markdown/templates_test.exs
@@ -0,0 +1,122 @@
+defmodule ExDoc.Formatter.MARKDOWN.TemplatesTest do
+ use ExUnit.Case, async: true
+
+ alias ExDoc.Formatter.MARKDOWN.Templates
+
+ defp source_url do
+ "https://github.com/elixir-lang/elixir"
+ end
+
+ defp homepage_url do
+ "https://elixir-lang.org"
+ end
+
+ defp doc_config(config \\ []) do
+ default = %ExDoc.Config{
+ project: "Elixir",
+ version: "1.0.1",
+ source_url_pattern: "#{source_url()}/blob/master/%{path}#L%{line}",
+ homepage_url: homepage_url(),
+ source_url: source_url(),
+ output: "test/tmp/markdown_templates"
+ }
+
+ struct(default, config)
+ end
+
+ defp get_module_page(names, config \\ []) do
+ config = doc_config(config)
+ {mods, []} = ExDoc.Retriever.docs_from_modules(names, config)
+ [mod | _] = ExDoc.Formatter.render_all(mods, [], ".md", config, highlight_tag: "samp")
+ Templates.module_page(config, mod)
+ end
+
+ setup_all do
+ # File.mkdir_p!("test/tmp/markdown_templates")
+ # File.cp_r!("formatters/markdown", "test/tmp/markdown_templates")
+ :ok
+ end
+
+ describe "module_page/2" do
+ test "generates only the module name when there's no more info" do
+ module_node = %ExDoc.ModuleNode{
+ module: XPTOModule,
+ doc: nil,
+ id: "XPTOModule",
+ title: "XPTOModule"
+ }
+
+ content = Templates.module_page(doc_config(), module_node)
+
+ assert content =~ ~r{#\s*XPTOModule\s*}
+ end
+
+ test "outputs the functions and docstrings" do
+ content = get_module_page([CompiledWithDocs])
+
+ assert content =~ ~r{#\s*CompiledWithDocs\s*}
+
+ assert content =~ ~s{## Table of Contents}
+
+ assert content =~
+ ~r{\n## .*Example.*}ms
+
+ assert content =~
+ ~r{\n### .*Example H3 heading.*}ms
+
+ assert content =~
+ ~r{moduledoc.*Example.*CompiledWithDocs\.example.*}ms
+
+ assert content =~ ~r{Some example}ms
+ assert content =~ ~r{example_without_docs().*}ms
+ assert content =~ ~r{example_1().* \(macro\)}ms
+
+ assert content =~ ~s{example(foo, bar \\\\ Baz)}
+ end
+
+ test "outputs function groups" do
+ content =
+ get_module_page([CompiledWithDocs],
+ groups_for_docs: [
+ "Example functions": &(&1[:purpose] == :example),
+ Legacy: &is_binary(&1[:deprecated])
+ ]
+ )
+
+ assert content =~ ~r{.*Example functions}ms
+ assert content =~ ~r{.*Legacy}ms
+ end
+
+ ## BEHAVIOURS
+
+ test "outputs behavior and callbacks" do
+ content = get_module_page([CustomBehaviourOne])
+
+ assert content =~
+ ~r{# CustomBehaviourOne \(behaviour\)}m
+
+ assert content =~ ~r{Callbacks}
+
+ content = get_module_page([CustomBehaviourTwo])
+
+ assert content =~
+ ~r{# CustomBehaviourTwo \(behaviour\)}m
+
+ assert content =~ ~r{Callbacks}
+ end
+
+ ## PROTOCOLS
+
+ test "outputs the protocol type" do
+ content = get_module_page([CustomProtocol])
+ assert content =~ ~r{# CustomProtocol \(protocol\)}m
+ end
+
+ ## TASKS
+
+ test "outputs the task type" do
+ content = get_module_page([Mix.Tasks.TaskWithDocs])
+ assert content =~ ~r{#\s*mix task_with_docs}m
+ end
+ 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..69b24b3de
--- /dev/null
+++ b/test/ex_doc/formatter/markdown_test.exs
@@ -0,0 +1,86 @@
+defmodule ExDoc.Formatter.MARKDOWNTest do
+ use ExUnit.Case, async: false
+
+ @moduletag :tmp_dir
+
+ @before_closing_body_tag_content_md "UNIQUE:
©BEFORE-CLOSING-BODY-TAG-MARKDOWN"
+
+ def before_closing_body_tag(:markdown), do: @before_closing_body_tag_content_md
+ def before_closing_body_tag(:markdown, name), do: "#{name}"
+
+ defp doc_config(%{tmp_dir: tmp_dir} = _context) do
+ [
+ app: :elixir,
+ project: "Elixir",
+ version: "1.0.1",
+ formatter: "markdown",
+ output: tmp_dir,
+ source_beam: "test/tmp/beam",
+ extras: ["test/fixtures/README.md"],
+ 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
+
+ defp generate_docs(_context, config) do
+ generate_docs(config)
+ end
+
+ test "generates a markdown index file in the default directory",
+ %{tmp_dir: tmp_dir} = context do
+ generate_docs(doc_config(context))
+ assert File.regular?(tmp_dir <> "/markdown/index.md")
+ end
+
+ test "generates a markdown file with erlang as proglang", %{tmp_dir: tmp_dir} = context do
+ config =
+ context
+ |> doc_config()
+ |> Keyword.put(:proglang, :erlang)
+ |> Keyword.update!(:skip_undefined_reference_warnings_on, &["test/fixtures/README.md" | &1])
+
+ generate_docs(config)
+ assert File.regular?(tmp_dir <> "/markdown/index.md")
+ end
+
+ test "generates a markdown file in specified output directory", %{tmp_dir: tmp_dir} = context do
+ config = doc_config(context, output: tmp_dir <> "/another_dir", main: "RandomError")
+ generate_docs(config)
+
+ assert File.regular?(tmp_dir <> "/another_dir/markdown/index.md")
+ end
+
+ test "generates the readme file", %{tmp_dir: tmp_dir} = context do
+ config = doc_config(context, main: "README")
+ generate_docs(context, config)
+
+ content = File.read!(tmp_dir <> "/markdown/readme.md")
+ assert content =~ ~r{`RandomError`\n}
+
+ assert content =~
+ ~r{\n`CustomBehaviourImpl.hello/1`\n}
+
+ assert content =~
+ ~r{\n`TypesAndSpecs.Sub`\n}
+
+ content = File.read!(tmp_dir <> "/markdown/index.md")
+ assert content =~ "Table of contents\n\n - [README](readme.md)"
+ end
+
+ test "includes before_closing_body_tag content", %{tmp_dir: tmp_dir} = context do
+ generate_docs(doc_config(context,
+ before_closing_body_tag: &before_closing_body_tag/1,
+ extras: ["test/fixtures/README.md"]
+ ))
+
+ content = File.read!(tmp_dir <> "/markdown/index.md")
+ assert content =~ @before_closing_body_tag_content_md
+ end
+end
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index b3f95396f..25140f323 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -799,8 +799,8 @@ defmodule ExDoc.Language.ErlangTest do
end
test "function - any", c do
- assert autolink_spec(~s"-spec foo() -> fun() | t().", c) ==
- ~s[foo() -> fun() |
t().]
+ assert autolink_spec(~s"-spec foo() -> fun((...) -> any()) | t().", c) ==
+ ~s[foo() -> fun((...) ->
any()) |
t().]
end
test "function - any arity", c do
diff --git a/test/ex_doc_test.exs b/test/ex_doc_test.exs
index 525b60f70..23571ec35 100644
--- a/test/ex_doc_test.exs
+++ b/test/ex_doc_test.exs
@@ -15,6 +15,10 @@ defmodule ExDocTest do
def run(modules, _filtered, config) do
{modules, config}
end
+
+ def run_with_extra_nodes(modules, _filtered, _extra_nodes, config) do
+ {modules, config}
+ end
end
test "uses custom markdown processor", %{tmp_dir: tmp_dir} do
diff --git a/test/mix/tasks/docs_test.exs b/test/mix/tasks/docs_test.exs
index 6019b62a0..cfd57c75e 100644
--- a/test/mix/tasks/docs_test.exs
+++ b/test/mix/tasks/docs_test.exs
@@ -28,7 +28,7 @@ defmodule Mix.Tasks.DocsTest do
{"ex_doc", "0.1.0",
[
formatter: "html",
- formatters: ["html", "epub"],
+ formatters: ["html", "epub", "markdown"],
deps: _,
apps: _,
source_beam: _,
@@ -37,7 +37,16 @@ defmodule Mix.Tasks.DocsTest do
{"ex_doc", "0.1.0",
[
formatter: "epub",
- formatters: ["html", "epub"],
+ formatters: ["html", "epub", "markdown"],
+ deps: _,
+ apps: _,
+ source_beam: _,
+ proglang: :elixir
+ ]},
+ {"ex_doc", "0.1.0",
+ [
+ formatter: "markdown",
+ formatters: ["html", "epub", "markdown"],
deps: _,
apps: _,
source_beam: _,
@@ -116,6 +125,15 @@ defmodule Mix.Tasks.DocsTest do
apps: _,
source_beam: _,
proglang: :elixir
+ ]},
+ {"ExDoc", "0.1.0",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, version: "0.1.0", name: "ExDoc")
end
@@ -141,6 +159,16 @@ defmodule Mix.Tasks.DocsTest do
apps: _,
source_beam: _,
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ main: "Sample",
+ apps: _,
+ source_beam: _,
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, docs: [main: Sample])
end
@@ -166,12 +194,22 @@ defmodule Mix.Tasks.DocsTest do
source_beam: _,
main: "another",
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ main: "another",
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, docs: [main: "another"])
end
test "accepts output in :output", %{tmp_dir: tmp_dir} = context do
- [{_, _, html_options}, {_, _, epub_options}] =
+ [{_, _, html_options}, {_, _, epub_options}, {_, _, markdown_options}] =
run_results = run(context, [], app: :ex_doc, docs: [output: tmp_dir <> "/hello"])
assert [
@@ -194,17 +232,28 @@ defmodule Mix.Tasks.DocsTest do
source_beam: _,
output: _,
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ output: _,
+ proglang: :elixir
]}
] = run_results
assert html_options[:output] == "#{tmp_dir}/hello"
assert epub_options[:output] == "#{tmp_dir}/hello"
+ assert markdown_options[:output] == "#{tmp_dir}/hello"
end
test "parses output with lower preference than options", %{tmp_dir: tmp_dir} = context do
output = tmp_dir <> "/world"
- [{_, _, html_options}, {_, _, epub_options}] =
+ [{_, _, html_options}, {_, _, epub_options}, {_, _, markdown_options}] =
run_results = run(context, ["-o", "#{output}"], app: :ex_doc, docs: [output: output])
assert [
@@ -227,11 +276,22 @@ defmodule Mix.Tasks.DocsTest do
source_beam: _,
output: _,
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ output: _,
+ proglang: :elixir
]}
] = run_results
assert html_options[:output] == "#{tmp_dir}/world"
assert epub_options[:output] == "#{tmp_dir}/world"
+ assert markdown_options[:output] == "#{tmp_dir}/world"
end
test "includes dependencies", context do
@@ -253,6 +313,15 @@ defmodule Mix.Tasks.DocsTest do
apps: _,
source_beam: _,
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: deps,
+ apps: _,
+ source_beam: _,
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, docs: [])
@@ -280,6 +349,15 @@ defmodule Mix.Tasks.DocsTest do
apps: _,
source_beam: _,
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: deps,
+ apps: _,
+ source_beam: _,
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, docs: [deps: [earmark_parser: "foo"]])
@@ -308,6 +386,16 @@ defmodule Mix.Tasks.DocsTest do
source_beam: _,
main: "another",
proglang: :elixir
+ ]},
+ {"ex_doc", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ main: "another",
+ proglang: :elixir
]}
] = run(context, [], app: :ex_doc, docs: fn -> [main: "another"] end)
end
@@ -336,6 +424,17 @@ defmodule Mix.Tasks.DocsTest do
homepage_url: "https://elixir-lang.org",
source_url: "https://github.com/elixir-lang/ex_doc",
proglang: :elixir
+ ]},
+ {"ExDoc", "1.2.3-dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: _,
+ source_beam: _,
+ homepage_url: "https://elixir-lang.org",
+ source_url: "https://github.com/elixir-lang/ex_doc",
+ proglang: :elixir
]}
] =
run(context, [],
@@ -347,7 +446,7 @@ defmodule Mix.Tasks.DocsTest do
proglang: :elixir
)
- assert [{"ex_doc", "dev", _}, {"ex_doc", "dev", _}] = run(context, [], app: :ex_doc)
+ assert [{"ex_doc", "dev", _}, {"ex_doc", "dev", _}, {"ex_doc", "dev", _}] = run(context, [], app: :ex_doc)
end
test "supports umbrella project", context do
@@ -370,6 +469,15 @@ defmodule Mix.Tasks.DocsTest do
apps: [:bar, :foo],
source_beam: _,
proglang: :elixir
+ ]},
+ {"umbrella", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: [:bar, :foo],
+ source_beam: _,
+ proglang: :elixir
]}
] = run(context, [], app: :umbrella, apps_path: "apps/", docs: [])
end)
@@ -397,6 +505,16 @@ defmodule Mix.Tasks.DocsTest do
source_beam: _,
ignore_apps: [:foo],
proglang: :elixir
+ ]},
+ {"umbrella", "dev",
+ [
+ formatter: "markdown",
+ formatters: _,
+ deps: _,
+ apps: [:bar],
+ source_beam: _,
+ ignore_apps: [:foo],
+ proglang: :elixir
]}
] = run(context, [], app: :umbrella, apps_path: "apps/", docs: [ignore_apps: [:foo]])
end)