From 8bd3cbae6fde8c7f6ce43861ab6491f25de97c93 Mon Sep 17 00:00:00 2001
From: Mayel de Borniol
Date: Sun, 8 Dec 2024 10:39:18 +0000
Subject: [PATCH 01/10] add markdown formatter / exporter
---
lib/ex_doc/cli.ex | 2 +-
lib/ex_doc/formatter/html/templates.ex | 5 +-
lib/ex_doc/formatter/markdown.ex | 126 +++++++++++
lib/ex_doc/formatter/markdown/assets.ex | 17 ++
lib/ex_doc/formatter/markdown/templates.ex | 197 ++++++++++++++++++
.../markdown/templates/detail_template.eex | 21 ++
.../markdown/templates/module_template.eex | 20 ++
.../markdown/templates/summary_template.eex | 13 ++
8 files changed, 399 insertions(+), 2 deletions(-)
create mode 100644 lib/ex_doc/formatter/markdown.ex
create mode 100644 lib/ex_doc/formatter/markdown/assets.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/summary_template.eex
diff --git a/lib/ex_doc/cli.ex b/lib/ex_doc/cli.ex
index 91403ff30..bace964f7 100644
--- a/lib/ex_doc/cli.ex
+++ b/lib/ex_doc/cli.ex
@@ -103,7 +103,7 @@ defmodule ExDoc.CLI do
defp normalize_formatters(opts) do
formatters =
case Keyword.get_values(opts, :formatter) do
- [] -> opts[:formatters] || ["html", "epub"]
+ [] -> opts[:formatters] || ["html", "epub", "markdown"]
values -> values
end
diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex
index 72407b672..435360578 100644
--- a/lib/ex_doc/formatter/html/templates.ex
+++ b/lib/ex_doc/formatter/html/templates.ex
@@ -64,7 +64,10 @@ defmodule ExDoc.Formatter.HTML.Templates do
Regex.replace(~r|(<[^>]*) id="[^"]*"([^>]*>)|, doc, ~S"\1\2", [])
end
- defp enc(binary), do: URI.encode(binary)
+ defp presence([]), do: nil
+ defp presence(other), do: other
+
+ def enc(binary), do: URI.encode(binary)
@doc """
Create a JS object which holds all the items displayed in the sidebar area
diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex
new file mode 100644
index 000000000..381b42041
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown.ex
@@ -0,0 +1,126 @@
+defmodule ExDoc.Formatter.Markdown do
+ @moduledoc false
+
+ @mimetype "text/markdown"
+ @assets_dir "MD/assets"
+ alias __MODULE__.{Assets, Templates}
+ alias ExDoc.Formatter.HTML
+ 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!(Path.join(config.output, "MD"))
+
+ project_nodes =
+ HTML.render_all(project_nodes, filtered_modules, ".md", config, highlight_tag: "samp")
+
+ nodes_map = %{
+ modules: HTML.filter_list(:module, project_nodes),
+ tasks: HTML.filter_list(:task, project_nodes)
+ }
+
+ extras =
+ config
+ |> HTML.build_extras(".xhtml")
+ |> Enum.chunk_by(& &1.group)
+ |> Enum.map(&{hd(&1).group, &1})
+
+ config = %{config | extras: extras}
+
+ static_files = HTML.generate_assets("MD", default_assets(config), config)
+ HTML.generate_logo(@assets_dir, config)
+ HTML.generate_cover(@assets_dir, config)
+
+ # generate_nav(config, nodes_map)
+ generate_extras(config)
+ generate_list(config, nodes_map.modules)
+ generate_list(config, nodes_map.tasks)
+
+ {:ok, epub} = generate_zip(config.output)
+ File.rm_rf!(config.output)
+ Path.relative_to_cwd(epub)
+ end
+
+ defp normalize_config(config) do
+ output =
+ config.output
+ |> Path.expand()
+ |> Path.join("#{config.project}")
+
+ %{config | output: output}
+ end
+
+ defp generate_extras(config) do
+ for {_title, extras} <- config.extras do
+ Enum.each(extras, fn %{id: id, title: title, title_content: _title_content, source: content} ->
+ output = "#{config.output}/MD/#{id}.md"
+ content = """
+ # #{title}
+
+ #{content}
+ """
+
+ if File.regular?(output) do
+ Utils.warn("file #{Path.relative_to_cwd(output)} already exists", [])
+ end
+
+ File.write!(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
+
+ defp generate_zip(output) do
+ :zip.create(
+ String.to_charlist("#{output}-markdown.zip"),
+ files_to_add(output),
+ compress: [
+ ~c".md",
+ ~c".jpg",
+ ~c".png"
+ ]
+ )
+ end
+
+ ## Helpers
+
+ defp default_assets(config) do
+ [
+ {Assets.dist(config.proglang), "MD/dist"},
+ {Assets.metainfo(), "META-INF"}
+ ]
+ end
+
+ defp files_to_add(path) do
+ Enum.reduce(Path.wildcard(Path.join(path, "**/*")), [], fn file, acc ->
+ case File.read(file) do
+ {:ok, bin} ->
+ [{file |> Path.relative_to(path) |> String.to_charlist(), bin} | acc]
+
+ {:error, _} ->
+ acc
+ end
+ end)
+ end
+
+ defp generate_module_page(module_node, config) do
+ content = Templates.module_page(config, module_node)
+ File.write("#{config.output}/MD/#{module_node.id}.md", content)
+ end
+
+end
diff --git a/lib/ex_doc/formatter/markdown/assets.ex b/lib/ex_doc/formatter/markdown/assets.ex
new file mode 100644
index 000000000..2a3041226
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/assets.ex
@@ -0,0 +1,17 @@
+defmodule ExDoc.Formatter.Markdown.Assets do
+ @moduledoc false
+
+ defmacrop embed_pattern(pattern) do
+ ["formatters/markdown", pattern]
+ |> Path.join()
+ |> Path.wildcard()
+ |> Enum.map(fn path ->
+ Module.put_attribute(__CALLER__.module, :external_resource, path)
+ {Path.basename(path), File.read!(path)}
+ end)
+ end
+
+ def dist(_proglang), do: []
+
+ def metainfo, do: embed_pattern("metainfo/*")
+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..ab9c5b498
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates.ex
@@ -0,0 +1,197 @@
+defmodule ExDoc.Formatter.Markdown.Templates do
+ @moduledoc false
+
+ require EEx
+
+ import ExDoc.Utils,
+ only: [before_closing_body_tag: 2, before_closing_head_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 """
+ 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}}), do: source
+ def node_doc(%{rendered_doc: source}), do: source
+
+ @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(nil), do: nil
+
+ def synopsis(doc) when is_binary(doc) do
+ doc =
+ case :binary.split(doc, "
") do
+ [left, _] -> String.trim_trailing(left, ": ")
+ [all] -> all
+ end
+
+ # Remove any anchors found in synopsis.
+ # Old Erlang docs placed anchors at the top of the documentation
+ # for links. Ideally they would have been removed but meanwhile
+ # it is simpler to guarantee they won't be duplicated in docs.
+ Regex.replace(~r|(<[^>]*) id="[^"]*"([^>]*>)|, doc, ~S"\1\2", [])
+ end
+
+ @doc """
+ Add link headings for the given `content`.
+
+ IDs are prefixed with `prefix`.
+
+ We only link `h2` and `h3` headers. This is kept consistent in ExDoc.SearchData.
+ """
+ @heading_regex ~r/<(h[23]).*?>(.*?)<\/\1>/m
+ @spec link_headings(String.t() | nil, String.t()) :: String.t() | nil
+ def link_headings(content, prefix \\ "")
+ def link_headings(nil, _), do: nil
+
+ def link_headings(content, prefix) do
+ @heading_regex
+ |> Regex.scan(content)
+ |> Enum.reduce({content, %{}}, fn [match, tag, title], {content, occurrences} ->
+ possible_id = text_to_id(title)
+ id_occurred = Map.get(occurrences, possible_id, 0)
+
+ anchor_id = if id_occurred >= 1, do: "#{possible_id}-#{id_occurred}", else: possible_id
+ replacement = link_heading(match, tag, title, anchor_id, prefix)
+ linked_content = String.replace(content, match, replacement, global: false)
+ incremented_occs = Map.put(occurrences, possible_id, id_occurred + 1)
+ {linked_content, incremented_occs}
+ end)
+ |> elem(0)
+ end
+
+ @class_regex ~r/[^"]+)")?.*?>/
+ @class_separator " "
+ defp link_heading(match, _tag, _title, "", _prefix), do: match
+
+ defp link_heading(match, tag, title, id, prefix) do
+ section_header_class_name = "section-heading"
+
+ # The Markdown syntax that we support for the admonition text
+ # blocks is something like this:
+ #
+ # > ### Never open this door! {: .warning}
+ # >
+ # > ...
+ #
+
+ """
+ ## [#{title}](##{prefix}#{id})
+ """
+ end
+
+ def link_moduledoc_headings(content) do
+ link_headings(content, "module-")
+ end
+
+ def link_detail_headings(content, prefix) do
+ link_headings(content, prefix <> "-")
+ end
+
+ @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.
+
+ # This template follows the EPUB Navigation Document Definition.
+
+ # See http://www.idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-nav.
+ # """
+ # EEx.function_from_file(
+ # :def,
+ # :nav_template,
+ # Path.expand("templates/nav_template.eex", __DIR__),
+ # [:config, :nodes],
+ # trim: true
+ # )
+
+ # @doc """
+ # Creates a new chapter when the user provides additional files.
+ # """
+ # EEx.function_from_file(
+ # :def,
+ # :extra_template,
+ # Path.expand("templates/extra_template.eex", __DIR__),
+ # [:config, :title, :title_content, :content],
+ # 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
+ # )
+
+ # "templates/media-types.txt"
+ # |> Path.expand(__DIR__)
+ # |> File.read!()
+ # |> String.split("\n", trim: true)
+ # |> Enum.each(fn line ->
+ # [extension, media] = String.split(line, ",")
+
+ # def media_type("." <> unquote(extension)) do
+ # unquote(media)
+ # end
+ # end)
+
+ # 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..32fd172ea
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates/detail_template.eex
@@ -0,0 +1,21 @@
+# <%=h node.signature %>
+
+<%= if node.source_url do %>
+[View Source](<%= 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 specs = H.get_specs(node) do %>
+<%= for spec <- specs do %>
+> <%= H.format_spec_attribute(module, node) %> <%= spec %>
+<% end %>
+<% end %>
+
+<%= link_detail_headings(node_doc(node), H.enc(node.id)) %>
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..750778cda
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates/module_template.eex
@@ -0,0 +1,20 @@
+# <%= module.title %> <%= H.module_type(module) %>
+
+<%= if deprecated = module.deprecated do %>
+> This <%= module.type %> is deprecated. <%=h deprecated %>.
+<% end %>
+
+<%= if doc = node_doc(module) do %>
+<%= H.link_moduledoc_headings(doc) %>
+<% end %>
+
+<%= if summary != [] do %>
+### Summary
+<%= for {name, nodes} <- summary, do: summary_template(name, nodes) %>
+<% end %>
+
+<%= for {name, nodes} <- summary, key = text_to_id(name) do %>
+## <%=h to_string(name) %>
+<%= for node <- nodes, do: detail_template(node, module) %>
+<% end %>
+<%= 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..52215651c
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates/summary_template.eex
@@ -0,0 +1,13 @@
+## <%= name %>
+<%= for node <- nodes do %>
+
+### <%=h node.signature %>
+
+<%= if deprecated = node.deprecated do %>
+> <%= h(deprecated) %>
+<% end %>
+
+<%= if doc = node_doc(node) do %>
+<%= synopsis(doc) %>
+<% end %>
+<% end %>
From d295d8e31ccf2f55faf3300d8b68d8a36c442786 Mon Sep 17 00:00:00 2001
From: Mayel de Borniol
Date: Thu, 26 Dec 2024 15:05:36 +0000
Subject: [PATCH 02/10] WIP for https://github.com/elixir-lang/ex_doc/pull/1976
---
lib/ex_doc.ex | 1 +
lib/ex_doc/cli.ex | 2 +-
.../html/templates/footer_template.eex | 6 +
.../html/templates/module_template.eex | 8 +
lib/ex_doc/formatter/markdown.ex | 49 +++--
lib/ex_doc/formatter/markdown/assets.ex | 2 +-
lib/ex_doc/formatter/markdown/templates.ex | 77 +++-----
.../templates/nav_grouped_item_template.eex | 8 +
.../markdown/templates/nav_item_template.eex | 6 +
.../markdown/templates/nav_template.eex | 9 +
.../formatter/markdown/templates_test.exs | 157 ++++++++++++++++
test/ex_doc/formatter/markdown_test.exs | 173 ++++++++++++++++++
12 files changed, 425 insertions(+), 73 deletions(-)
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 test/ex_doc/formatter/markdown/templates_test.exs
create mode 100644 test/ex_doc/formatter/markdown_test.exs
diff --git a/lib/ex_doc.ex b/lib/ex_doc.ex
index c108c3560..4fdf725a3 100644
--- a/lib/ex_doc.ex
+++ b/lib/ex_doc.ex
@@ -44,6 +44,7 @@ defmodule ExDoc do
if Code.ensure_loaded?(modname) do
modname
else
+ IO.inspect(modname)
raise "formatter module #{inspect(argname)} not found"
end
end
diff --git a/lib/ex_doc/cli.ex b/lib/ex_doc/cli.ex
index bace964f7..91403ff30 100644
--- a/lib/ex_doc/cli.ex
+++ b/lib/ex_doc/cli.ex
@@ -103,7 +103,7 @@ defmodule ExDoc.CLI do
defp normalize_formatters(opts) do
formatters =
case Keyword.get_values(opts, :formatter) do
- [] -> opts[:formatters] || ["html", "epub", "markdown"]
+ [] -> opts[:formatters] || ["html", "epub"]
values -> values
end
diff --git a/lib/ex_doc/formatter/html/templates/footer_template.eex b/lib/ex_doc/formatter/html/templates/footer_template.eex
index 5488a0212..2f0042019 100644
--- a/lib/ex_doc/formatter/html/templates/footer_template.eex
+++ b/lib/ex_doc/formatter/html/templates/footer_template.eex
@@ -22,6 +22,12 @@
Download ePub version
<% end %>
+
+ <%= if "markdown" in config.formatters do %>
+
+ Download Markdown version
+
+ <% end %>
diff --git a/lib/ex_doc/formatter/html/templates/module_template.eex b/lib/ex_doc/formatter/html/templates/module_template.eex
index b509f167b..f057d3f94 100644
--- a/lib/ex_doc/formatter/html/templates/module_template.eex
+++ b/lib/ex_doc/formatter/html/templates/module_template.eex
@@ -9,6 +9,14 @@
View Source
<% end %>
+ <%= if "markdown" in config.formatters do %>
+
+ <%= IO.inspect(module).title %>
+
+ Download Markdown version
+
+ <% end %>
+
<%= module.title %> <%= module_type(module) %>
(<%= config.project %> v<%= config.version %>)
<%= for annotation <- module.annotations do %>
diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex
index 381b42041..ca0e49178 100644
--- a/lib/ex_doc/formatter/markdown.ex
+++ b/lib/ex_doc/formatter/markdown.ex
@@ -1,7 +1,6 @@
-defmodule ExDoc.Formatter.Markdown do
+defmodule ExDoc.Formatter.MARKDOWN do
@moduledoc false
- @mimetype "text/markdown"
@assets_dir "MD/assets"
alias __MODULE__.{Assets, Templates}
alias ExDoc.Formatter.HTML
@@ -28,24 +27,24 @@ defmodule ExDoc.Formatter.Markdown do
extras =
config
- |> HTML.build_extras(".xhtml")
+ |> HTML.build_extras(".md")
|> Enum.chunk_by(& &1.group)
|> Enum.map(&{hd(&1).group, &1})
config = %{config | extras: extras}
- static_files = HTML.generate_assets("MD", default_assets(config), config)
- HTML.generate_logo(@assets_dir, config)
- HTML.generate_cover(@assets_dir, config)
-
- # generate_nav(config, nodes_map)
+ generate_nav(config, nodes_map)
generate_extras(config)
generate_list(config, nodes_map.modules)
generate_list(config, nodes_map.tasks)
- {:ok, epub} = generate_zip(config.output)
- File.rm_rf!(config.output)
- Path.relative_to_cwd(epub)
+ # if config[:generate_zip] do # TODO: add a command line flag?
+ # {:ok, zip} = generate_zip(config.output)
+ # File.rm_rf!(config.output)
+ # Path.relative_to_cwd(zip)
+ # else
+ config.output |> Path.join("index.md") |> Path.relative_to_cwd()
+ # end
end
defp normalize_config(config) do
@@ -57,6 +56,23 @@ defmodule ExDoc.Formatter.Markdown do
%{config | output: output}
end
+ defp normalize_output(output) do
+ output
+ |> String.replace(~r/\r\n|\r|\n/, "\n")
+ |> String.replace(~r/\n{2,}/, "\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}/MD/index.md", content)
+ end
+
defp generate_extras(config) do
for {_title, extras} <- config.extras do
Enum.each(extras, fn %{id: id, title: title, title_content: _title_content, source: content} ->
@@ -66,6 +82,7 @@ defmodule ExDoc.Formatter.Markdown do
#{content}
"""
+ |> normalize_output()
if File.regular?(output) do
Utils.warn("file #{Path.relative_to_cwd(output)} already exists", [])
@@ -77,8 +94,6 @@ defmodule ExDoc.Formatter.Markdown do
end
-
-
defp generate_list(config, nodes) do
nodes
|> Task.async_stream(&generate_module_page(&1, config), timeout: :infinity)
@@ -99,13 +114,6 @@ defmodule ExDoc.Formatter.Markdown do
## Helpers
- defp default_assets(config) do
- [
- {Assets.dist(config.proglang), "MD/dist"},
- {Assets.metainfo(), "META-INF"}
- ]
- end
-
defp files_to_add(path) do
Enum.reduce(Path.wildcard(Path.join(path, "**/*")), [], fn file, acc ->
case File.read(file) do
@@ -120,6 +128,7 @@ defmodule ExDoc.Formatter.Markdown do
defp generate_module_page(module_node, config) do
content = Templates.module_page(config, module_node)
+ |> normalize_output()
File.write("#{config.output}/MD/#{module_node.id}.md", content)
end
diff --git a/lib/ex_doc/formatter/markdown/assets.ex b/lib/ex_doc/formatter/markdown/assets.ex
index 2a3041226..5001fae5b 100644
--- a/lib/ex_doc/formatter/markdown/assets.ex
+++ b/lib/ex_doc/formatter/markdown/assets.ex
@@ -1,4 +1,4 @@
-defmodule ExDoc.Formatter.Markdown.Assets do
+defmodule ExDoc.Formatter.MARKDOWN.Assets do
@moduledoc false
defmacrop embed_pattern(pattern) do
diff --git a/lib/ex_doc/formatter/markdown/templates.ex b/lib/ex_doc/formatter/markdown/templates.ex
index ab9c5b498..da57e5341 100644
--- a/lib/ex_doc/formatter/markdown/templates.ex
+++ b/lib/ex_doc/formatter/markdown/templates.ex
@@ -1,10 +1,10 @@
-defmodule ExDoc.Formatter.Markdown.Templates do
+defmodule ExDoc.Formatter.MARKDOWN.Templates do
@moduledoc false
require EEx
import ExDoc.Utils,
- only: [before_closing_body_tag: 2, before_closing_head_tag: 2, h: 1, text_to_id: 1]
+ only: [before_closing_body_tag: 2, h: 1, text_to_id: 1]
alias ExDoc.Formatter.HTML.Templates, as: H
@@ -119,48 +119,34 @@ defmodule ExDoc.Formatter.Markdown.Templates do
trim: true
)
- # @doc """
- # Creates the table of contents.
-
- # This template follows the EPUB Navigation Document Definition.
-
- # See http://www.idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-nav.
- # """
- # EEx.function_from_file(
- # :def,
- # :nav_template,
- # Path.expand("templates/nav_template.eex", __DIR__),
- # [:config, :nodes],
- # trim: true
- # )
+ @doc """
+ Creates the table of contents.
- # @doc """
- # Creates a new chapter when the user provides additional files.
- # """
- # EEx.function_from_file(
- # :def,
- # :extra_template,
- # Path.expand("templates/extra_template.eex", __DIR__),
- # [:config, :title, :title_content, :content],
- # trim: true
- # )
+ """
+ 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_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,
+ :nav_grouped_item_template,
+ Path.expand("templates/nav_grouped_item_template.eex", __DIR__),
+ [:nodes],
+ trim: true
+ )
# EEx.function_from_file(
# :defp,
@@ -170,17 +156,6 @@ defmodule ExDoc.Formatter.Markdown.Templates do
# trim: true
# )
- # "templates/media-types.txt"
- # |> Path.expand(__DIR__)
- # |> File.read!()
- # |> String.split("\n", trim: true)
- # |> Enum.each(fn line ->
- # [extension, media] = String.split(line, ",")
-
- # def media_type("." <> unquote(extension)) do
- # unquote(media)
- # end
- # end)
# def media_type(_arg), do: nil
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..aaa568662
--- /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 %>
+1. [<%=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..aa35d02df
--- /dev/null
+++ b/lib/ex_doc/formatter/markdown/templates/nav_template.eex
@@ -0,0 +1,9 @@
+# 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/test/ex_doc/formatter/markdown/templates_test.exs b/test/ex_doc/formatter/markdown/templates_test.exs
new file mode 100644
index 000000000..69c3cbc97
--- /dev/null
+++ b/test/ex_doc/formatter/markdown/templates_test.exs
@@ -0,0 +1,157 @@
+defmodule ExDoc.Formatter.MARKDOWN.TemplatesTest do
+ use ExUnit.Case, async: true
+
+ alias ExDoc.Formatter.HTML
+ 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 | _] = HTML.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 "content_template/5" do
+ test "includes logo as a resource if specified in the config" do
+ nodes = %{modules: [], tasks: []}
+
+ content =
+ [logo: "my_logo.png"]
+ |> doc_config()
+ |> Templates.content_template(nodes, "uuid", "datetime", _static_files = [])
+
+ assert content =~ ~S| |
+ end
+
+
+ test "includes modules as a resource" do
+ module_node = %ExDoc.ModuleNode{
+ module: XPTOModule,
+ doc: nil,
+ id: "XPTOModule",
+ title: "XPTOModule"
+ }
+
+ nodes = %{modules: [module_node], tasks: []}
+
+ content =
+ Templates.content_template(doc_config(), nodes, "uuid", "datetime", _static_files = [])
+
+ assert content =~
+ ~S| |
+
+ assert content =~ ~S||
+ end
+ 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{# Summary}
+
+ assert content =~
+ ~r{## .*Example.*}ms
+
+ assert content =~
+ ~r{### .*Example H3 heading.*}ms
+
+ assert content =~
+ ~r{moduledoc.*Example.*CompiledWithDocs\.example.*}ms
+
+ assert content =~ ~r{example/2.*Some example}ms
+ assert content =~ ~r{example_without_docs/0.*}ms
+ assert content =~ ~r{example_1/0.*> \(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{# \s*CustomBehaviourOne\s*behaviour\s*}m
+
+ assert content =~ ~r{Callbacks}
+
+ content = get_module_page([CustomBehaviourTwo])
+
+ assert content =~
+ ~r{# \s*CustomBehaviourTwo\s*behaviour\s*}m
+
+ assert content =~ ~r{Callbacks}
+ end
+
+ ## PROTOCOLS
+
+ test "outputs the protocol type" do
+ content = get_module_page([CustomProtocol])
+ assert content =~ ~r{# \s*CustomProtocol\s*protocol\s*}m
+ end
+
+ ## TASKS
+
+ test "outputs the task type" do
+ content = get_module_page([Mix.Tasks.TaskWithDocs])
+ assert content =~ ~r{# \s*mix task_with_docs\s*}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..9af39ecf6
--- /dev/null
+++ b/test/ex_doc/formatter/markdown_test.exs
@@ -0,0 +1,173 @@
+defmodule ExDoc.Formatter.MARKDOWNTest do
+ use ExUnit.Case, async: false
+
+ import ExUnit.CaptureIO
+
+ alias ExDoc.Utils
+
+ @moduletag :tmp_dir
+
+ @before_closing_body_tag_content_md "UNIQUE:©BEFORE-CLOSING-BODY-TAG-HTML"
+
+ defp 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 <> "/markdown",
+ 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 nav file in the default directory", %{tmp_dir: tmp_dir} = context do
+ generate_docs(doc_config(context))
+ assert File.regular?(tmp_dir <> "/markdown/Elixir/MD/nav.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/Elixir/MD/nav.md")
+ end
+
+ test "generates a markdown file in specified output directory", %{tmp_dir: tmp_dir} = context do
+ config = doc_config(context, output: tmp_dir <> "/markdown/another_dir", main: "RandomError")
+ generate_docs(config)
+
+ assert File.regular?(tmp_dir <> "/markdown/another_dir/nav.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/Elixir/MD/readme.md")
+ assert content =~ ~r{README [^<]*}
+ assert content =~ ~r{RandomError
}
+
+ assert content =~
+ ~r{CustomBehaviourImpl.hello/1
}
+
+ assert content =~
+ ~r{TypesAndSpecs.Sub
}
+
+ content = File.read!(tmp_dir <> "/markdown/Elixir/MD/nav.md")
+ assert content =~ ~r{README}
+ end
+
+ test "uses samp as highlight tag for markdown", %{tmp_dir: tmp_dir} = context do
+ generate_docs(context, doc_config(context))
+
+ assert File.read!(tmp_dir <> "/markdown/Elixir/MD/CompiledWithDocs.md") =~
+ "CompiledWithDocs<\/samp>"
+ end
+
+ @example_basenames [
+ # "structural" pages
+ "nav.md",
+ "readme.md",
+ # "module pages"
+ "CompiledWithDocs.md",
+ "CompiledWithDocs.Nested.md"
+ ]
+
+ test "before_closing_*_tags required by the user are in the right place",
+ %{tmp_dir: tmp_dir} = context do
+ generate_docs(
+ context,
+ doc_config(context,
+ before_closing_body_tag: &before_closing_body_tag/1
+ )
+ )
+
+ dir = tmp_dir <> "/markdown/Elixir/MD"
+
+ for basename <- @example_basenames do
+ content = File.read!(Path.join(dir, basename))
+ assert content =~ ~r[#{@before_closing_body_tag_content_md}\s]
+ end
+ end
+
+ test "before_closing_*_tags required by the user are in the right place using map",
+ %{tmp_dir: tmp_dir} = context do
+ generate_docs(
+ context,
+ doc_config(context,
+ before_closing_body_tag: %{markdown: "StaticDemo
"}
+ )
+ )
+
+ dir = tmp_dir <> "/markdown/Elixir/MD"
+
+ for basename <- @example_basenames do
+ content = File.read!(Path.join(dir, basename))
+ assert content =~ ~r[StaticDemo
\s]
+ end
+ end
+
+ test "before_closing_*_tags required by the user are in the right place using a MFA",
+ %{tmp_dir: tmp_dir} = context do
+ generate_docs(
+ context,
+ doc_config(context,
+ before_closing_body_tag: {__MODULE__, :before_closing_body_tag, ["Demo"]}
+ )
+ )
+
+ dir = tmp_dir <> "/markdown/Elixir/MD"
+
+ for basename <- @example_basenames do
+ content = File.read!(Path.join(dir, basename))
+ assert content =~ ~r[Demo
\s]
+ end
+ end
+
+ test "assets required by the user end up in the right place", %{tmp_dir: tmp_dir} = context do
+ File.mkdir_p!("test/tmp/markdown_assets/hello")
+ File.touch!("test/tmp/markdown_assets/hello/world.png")
+ File.touch!("test/tmp/markdown_assets/hello/world.pdf")
+
+ generate_docs(
+ context,
+ doc_config(context,
+ assets: %{"test/tmp/markdown_assets" => "assets"},
+ logo: "test/fixtures/elixir.png",
+ cover: "test/fixtures/elixir.png"
+ )
+ )
+
+ assert File.regular?(tmp_dir <> "/markdown/assets/hello/world.png")
+ assert File.regular?(tmp_dir <> "/markdown/assets/hello/world.pdf")
+ assert File.regular?(tmp_dir <> "/markdown/assets/logo.png")
+ assert File.regular?(tmp_dir <> "/markdown/assets/cover.png")
+ after
+ File.rm_rf!("test/tmp/markdown_assets")
+ end
+
+end
From 23b5f0141b0993befc7c0b83ce5db4f589430035 Mon Sep 17 00:00:00 2001
From: Mayel de Borniol
Date: Thu, 26 Dec 2024 15:56:45 +0000
Subject: [PATCH 03/10] cleanup
---
lib/ex_doc.ex | 1 -
lib/ex_doc/formatter/markdown.ex | 25 +++++++++----------------
lib/ex_doc/formatter/markdown/assets.ex | 17 -----------------
3 files changed, 9 insertions(+), 34 deletions(-)
delete mode 100644 lib/ex_doc/formatter/markdown/assets.ex
diff --git a/lib/ex_doc.ex b/lib/ex_doc.ex
index 4fdf725a3..c108c3560 100644
--- a/lib/ex_doc.ex
+++ b/lib/ex_doc.ex
@@ -44,7 +44,6 @@ defmodule ExDoc do
if Code.ensure_loaded?(modname) do
modname
else
- IO.inspect(modname)
raise "formatter module #{inspect(argname)} not found"
end
end
diff --git a/lib/ex_doc/formatter/markdown.ex b/lib/ex_doc/formatter/markdown.ex
index ca0e49178..9ea95c33c 100644
--- a/lib/ex_doc/formatter/markdown.ex
+++ b/lib/ex_doc/formatter/markdown.ex
@@ -1,8 +1,7 @@
defmodule ExDoc.Formatter.MARKDOWN do
@moduledoc false
- @assets_dir "MD/assets"
- alias __MODULE__.{Assets, Templates}
+ alias __MODULE__.{Templates}
alias ExDoc.Formatter.HTML
alias ExDoc.Utils
@@ -15,7 +14,7 @@ defmodule ExDoc.Formatter.MARKDOWN do
config = normalize_config(config)
File.rm_rf!(config.output)
- File.mkdir_p!(Path.join(config.output, "MD"))
+ File.mkdir_p!(config.output)
project_nodes =
HTML.render_all(project_nodes, filtered_modules, ".md", config, highlight_tag: "samp")
@@ -51,7 +50,7 @@ defmodule ExDoc.Formatter.MARKDOWN do
output =
config.output
|> Path.expand()
- |> Path.join("#{config.project}")
+ |> Path.join("markdown")
%{config | output: output}
end
@@ -59,7 +58,7 @@ defmodule ExDoc.Formatter.MARKDOWN do
defp normalize_output(output) do
output
|> String.replace(~r/\r\n|\r|\n/, "\n")
- |> String.replace(~r/\n{2,}/, "\n")
+ |> String.replace(~r/\n{3,}/, "\n\n")
end
defp generate_nav(config, nodes) do
@@ -70,25 +69,19 @@ defmodule ExDoc.Formatter.MARKDOWN do
content = Templates.nav_template(config, nodes)
|> normalize_output()
- File.write("#{config.output}/MD/index.md", content)
+ 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, title: title, title_content: _title_content, source: content} ->
- output = "#{config.output}/MD/#{id}.md"
- content = """
- # #{title}
-
- #{content}
- """
- |> normalize_output()
+ 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, content)
+ File.write!(output, normalize_output(content))
end)
end
end
@@ -129,7 +122,7 @@ defmodule ExDoc.Formatter.MARKDOWN do
defp generate_module_page(module_node, config) do
content = Templates.module_page(config, module_node)
|> normalize_output()
- File.write("#{config.output}/MD/#{module_node.id}.md", content)
+ File.write("#{config.output}/#{module_node.id}.md", content)
end
end
diff --git a/lib/ex_doc/formatter/markdown/assets.ex b/lib/ex_doc/formatter/markdown/assets.ex
deleted file mode 100644
index 5001fae5b..000000000
--- a/lib/ex_doc/formatter/markdown/assets.ex
+++ /dev/null
@@ -1,17 +0,0 @@
-defmodule ExDoc.Formatter.MARKDOWN.Assets do
- @moduledoc false
-
- defmacrop embed_pattern(pattern) do
- ["formatters/markdown", pattern]
- |> Path.join()
- |> Path.wildcard()
- |> Enum.map(fn path ->
- Module.put_attribute(__CALLER__.module, :external_resource, path)
- {Path.basename(path), File.read!(path)}
- end)
- end
-
- def dist(_proglang), do: []
-
- def metainfo, do: embed_pattern("metainfo/*")
-end
From 6bd15cc7b8087f0b152ceb89cee5c9b0df6a94e5 Mon Sep 17 00:00:00 2001
From: Mayel de Borniol
Date: Fri, 27 Dec 2024 15:42:48 +0000
Subject: [PATCH 04/10] update footer links & md tests
---
lib/ex_doc/formatter/html/templates.ex | 15 +++
.../html/templates/footer_template.eex | 46 ++++---
.../html/templates/module_template.eex | 7 --
lib/ex_doc/formatter/markdown.ex | 38 ++----
lib/ex_doc/formatter/markdown/templates.ex | 15 ++-
.../markdown/templates/detail_template.eex | 6 +-
.../markdown/templates/module_template.eex | 2 +-
lib/ex_doc/language/elixir.ex | 2 +-
.../formatter/markdown/templates_test.exs | 50 ++------
test/ex_doc/formatter/markdown_test.exs | 118 ++----------------
10 files changed, 90 insertions(+), 209 deletions(-)
diff --git a/lib/ex_doc/formatter/html/templates.ex b/lib/ex_doc/formatter/html/templates.ex
index 435360578..235e441f1 100644
--- a/lib/ex_doc/formatter/html/templates.ex
+++ b/lib/ex_doc/formatter/html/templates.ex
@@ -209,6 +209,21 @@ defmodule ExDoc.Formatter.HTML.Templates do
defp relative_asset([h | _], output, _pattern), do: Path.relative_to(h, output)
+ defp get_hex_url(config, source_path) do
+ case config.package do
+ nil ->
+ nil
+
+ package ->
+ base_url = "https://preview.hex.pm/preview/#{package}/#{config.version}"
+ if source_path, do: "#{base_url}/show/#{source_path}", else: base_url
+ end
+ end
+
+ defp get_markdown_path(node) do
+ if node && node.id, do: URI.encode(node.id), else: "index"
+ end
+
# TODO: Move link_headings and friends to html.ex or even to autolinking code,
# so content is built with it upfront instead of added at the template level.
diff --git a/lib/ex_doc/formatter/html/templates/footer_template.eex b/lib/ex_doc/formatter/html/templates/footer_template.eex
index 2f0042019..b9feb54ef 100644
--- a/lib/ex_doc/formatter/html/templates/footer_template.eex
+++ b/lib/ex_doc/formatter/html/templates/footer_template.eex
@@ -1,33 +1,43 @@