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 = ""
+ 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 25490be56..4964c1d14 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)
@@ -183,6 +189,7 @@ defmodule ExDoc.Formatter do
id = input_options[:filename] || input |> filename_to_title() |> Utils.text_to_id()
source_file = input_options[:source] || input
opts = [file: source_file, line: 1]
+ ext = Keyword.fetch!(autolink_opts, :ext)
{extension, source, ast} =
case extension_name(input) do
@@ -198,7 +205,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