Skip to content

Commit 8bd3cba

Browse files
committed
add markdown formatter / exporter
1 parent f72d6d5 commit 8bd3cba

File tree

8 files changed

+399
-2
lines changed

8 files changed

+399
-2
lines changed

lib/ex_doc/cli.ex

+1-1
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ defmodule ExDoc.CLI do
103103
defp normalize_formatters(opts) do
104104
formatters =
105105
case Keyword.get_values(opts, :formatter) do
106-
[] -> opts[:formatters] || ["html", "epub"]
106+
[] -> opts[:formatters] || ["html", "epub", "markdown"]
107107
values -> values
108108
end
109109

lib/ex_doc/formatter/html/templates.ex

+4-1
Original file line numberDiff line numberDiff line change
@@ -64,7 +64,10 @@ defmodule ExDoc.Formatter.HTML.Templates do
6464
Regex.replace(~r|(<[^>]*) id="[^"]*"([^>]*>)|, doc, ~S"\1\2", [])
6565
end
6666

67-
defp enc(binary), do: URI.encode(binary)
67+
defp presence([]), do: nil
68+
defp presence(other), do: other
69+
70+
def enc(binary), do: URI.encode(binary)
6871

6972
@doc """
7073
Create a JS object which holds all the items displayed in the sidebar area

lib/ex_doc/formatter/markdown.ex

+126
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,126 @@
1+
defmodule ExDoc.Formatter.Markdown do
2+
@moduledoc false
3+
4+
@mimetype "text/markdown"
5+
@assets_dir "MD/assets"
6+
alias __MODULE__.{Assets, Templates}
7+
alias ExDoc.Formatter.HTML
8+
alias ExDoc.Utils
9+
10+
@doc """
11+
Generates Markdown documentation for the given modules.
12+
"""
13+
@spec run([ExDoc.ModuleNode.t()], [ExDoc.ModuleNode.t()], ExDoc.Config.t()) :: String.t()
14+
def run(project_nodes, filtered_modules, config) when is_map(config) do
15+
Utils.unset_warned()
16+
17+
config = normalize_config(config)
18+
File.rm_rf!(config.output)
19+
File.mkdir_p!(Path.join(config.output, "MD"))
20+
21+
project_nodes =
22+
HTML.render_all(project_nodes, filtered_modules, ".md", config, highlight_tag: "samp")
23+
24+
nodes_map = %{
25+
modules: HTML.filter_list(:module, project_nodes),
26+
tasks: HTML.filter_list(:task, project_nodes)
27+
}
28+
29+
extras =
30+
config
31+
|> HTML.build_extras(".xhtml")
32+
|> Enum.chunk_by(& &1.group)
33+
|> Enum.map(&{hd(&1).group, &1})
34+
35+
config = %{config | extras: extras}
36+
37+
static_files = HTML.generate_assets("MD", default_assets(config), config)
38+
HTML.generate_logo(@assets_dir, config)
39+
HTML.generate_cover(@assets_dir, config)
40+
41+
# generate_nav(config, nodes_map)
42+
generate_extras(config)
43+
generate_list(config, nodes_map.modules)
44+
generate_list(config, nodes_map.tasks)
45+
46+
{:ok, epub} = generate_zip(config.output)
47+
File.rm_rf!(config.output)
48+
Path.relative_to_cwd(epub)
49+
end
50+
51+
defp normalize_config(config) do
52+
output =
53+
config.output
54+
|> Path.expand()
55+
|> Path.join("#{config.project}")
56+
57+
%{config | output: output}
58+
end
59+
60+
defp generate_extras(config) do
61+
for {_title, extras} <- config.extras do
62+
Enum.each(extras, fn %{id: id, title: title, title_content: _title_content, source: content} ->
63+
output = "#{config.output}/MD/#{id}.md"
64+
content = """
65+
# #{title}
66+
67+
#{content}
68+
"""
69+
70+
if File.regular?(output) do
71+
Utils.warn("file #{Path.relative_to_cwd(output)} already exists", [])
72+
end
73+
74+
File.write!(output, content)
75+
end)
76+
end
77+
end
78+
79+
80+
81+
82+
defp generate_list(config, nodes) do
83+
nodes
84+
|> Task.async_stream(&generate_module_page(&1, config), timeout: :infinity)
85+
|> Enum.map(&elem(&1, 1))
86+
end
87+
88+
defp generate_zip(output) do
89+
:zip.create(
90+
String.to_charlist("#{output}-markdown.zip"),
91+
files_to_add(output),
92+
compress: [
93+
~c".md",
94+
~c".jpg",
95+
~c".png"
96+
]
97+
)
98+
end
99+
100+
## Helpers
101+
102+
defp default_assets(config) do
103+
[
104+
{Assets.dist(config.proglang), "MD/dist"},
105+
{Assets.metainfo(), "META-INF"}
106+
]
107+
end
108+
109+
defp files_to_add(path) do
110+
Enum.reduce(Path.wildcard(Path.join(path, "**/*")), [], fn file, acc ->
111+
case File.read(file) do
112+
{:ok, bin} ->
113+
[{file |> Path.relative_to(path) |> String.to_charlist(), bin} | acc]
114+
115+
{:error, _} ->
116+
acc
117+
end
118+
end)
119+
end
120+
121+
defp generate_module_page(module_node, config) do
122+
content = Templates.module_page(config, module_node)
123+
File.write("#{config.output}/MD/#{module_node.id}.md", content)
124+
end
125+
126+
end
+17
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
defmodule ExDoc.Formatter.Markdown.Assets do
2+
@moduledoc false
3+
4+
defmacrop embed_pattern(pattern) do
5+
["formatters/markdown", pattern]
6+
|> Path.join()
7+
|> Path.wildcard()
8+
|> Enum.map(fn path ->
9+
Module.put_attribute(__CALLER__.module, :external_resource, path)
10+
{Path.basename(path), File.read!(path)}
11+
end)
12+
end
13+
14+
def dist(_proglang), do: []
15+
16+
def metainfo, do: embed_pattern("metainfo/*")
17+
end
+197
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,197 @@
1+
defmodule ExDoc.Formatter.Markdown.Templates do
2+
@moduledoc false
3+
4+
require EEx
5+
6+
import ExDoc.Utils,
7+
only: [before_closing_body_tag: 2, before_closing_head_tag: 2, h: 1, text_to_id: 1]
8+
9+
alias ExDoc.Formatter.HTML.Templates, as: H
10+
11+
@doc """
12+
Generate content from the module template for a given `node`
13+
"""
14+
def module_page(config, module_node) do
15+
summary = H.module_summary(module_node)
16+
module_template(config, module_node, summary)
17+
end
18+
19+
@doc """
20+
Generated ID for static file
21+
"""
22+
def static_file_to_id(static_file) do
23+
static_file |> Path.basename() |> text_to_id()
24+
end
25+
26+
def node_doc(%{source_doc: %{"en"=> source}}), do: source
27+
def node_doc(%{rendered_doc: source}), do: source
28+
29+
@doc """
30+
Gets the first paragraph of the documentation of a node. It strips
31+
surrounding white-spaces and trailing `:`.
32+
33+
If `doc` is `nil`, it returns `nil`.
34+
"""
35+
@spec synopsis(String.t()) :: String.t()
36+
@spec synopsis(nil) :: nil
37+
def synopsis(nil), do: nil
38+
39+
def synopsis(doc) when is_binary(doc) do
40+
doc =
41+
case :binary.split(doc, "</p>") do
42+
[left, _] -> String.trim_trailing(left, ": ")
43+
[all] -> all
44+
end
45+
46+
# Remove any anchors found in synopsis.
47+
# Old Erlang docs placed anchors at the top of the documentation
48+
# for links. Ideally they would have been removed but meanwhile
49+
# it is simpler to guarantee they won't be duplicated in docs.
50+
Regex.replace(~r|(<[^>]*) id="[^"]*"([^>]*>)|, doc, ~S"\1\2", [])
51+
end
52+
53+
@doc """
54+
Add link headings for the given `content`.
55+
56+
IDs are prefixed with `prefix`.
57+
58+
We only link `h2` and `h3` headers. This is kept consistent in ExDoc.SearchData.
59+
"""
60+
@heading_regex ~r/<(h[23]).*?>(.*?)<\/\1>/m
61+
@spec link_headings(String.t() | nil, String.t()) :: String.t() | nil
62+
def link_headings(content, prefix \\ "")
63+
def link_headings(nil, _), do: nil
64+
65+
def link_headings(content, prefix) do
66+
@heading_regex
67+
|> Regex.scan(content)
68+
|> Enum.reduce({content, %{}}, fn [match, tag, title], {content, occurrences} ->
69+
possible_id = text_to_id(title)
70+
id_occurred = Map.get(occurrences, possible_id, 0)
71+
72+
anchor_id = if id_occurred >= 1, do: "#{possible_id}-#{id_occurred}", else: possible_id
73+
replacement = link_heading(match, tag, title, anchor_id, prefix)
74+
linked_content = String.replace(content, match, replacement, global: false)
75+
incremented_occs = Map.put(occurrences, possible_id, id_occurred + 1)
76+
{linked_content, incremented_occs}
77+
end)
78+
|> elem(0)
79+
end
80+
81+
@class_regex ~r/<h[23].*?(\sclass="(?<class>[^"]+)")?.*?>/
82+
@class_separator " "
83+
defp link_heading(match, _tag, _title, "", _prefix), do: match
84+
85+
defp link_heading(match, tag, title, id, prefix) do
86+
section_header_class_name = "section-heading"
87+
88+
# The Markdown syntax that we support for the admonition text
89+
# blocks is something like this:
90+
#
91+
# > ### Never open this door! {: .warning}
92+
# >
93+
# > ...
94+
#
95+
96+
"""
97+
## [#{title}](##{prefix}#{id})
98+
"""
99+
end
100+
101+
def link_moduledoc_headings(content) do
102+
link_headings(content, "module-")
103+
end
104+
105+
def link_detail_headings(content, prefix) do
106+
link_headings(content, prefix <> "-")
107+
end
108+
109+
@doc """
110+
Creates a chapter which contains all the details about an individual module.
111+
112+
This chapter can include the following sections: *functions*, *types*, *callbacks*.
113+
"""
114+
EEx.function_from_file(
115+
:def,
116+
:module_template,
117+
Path.expand("templates/module_template.eex", __DIR__),
118+
[:config, :module, :summary],
119+
trim: true
120+
)
121+
122+
# @doc """
123+
# Creates the table of contents.
124+
125+
# This template follows the EPUB Navigation Document Definition.
126+
127+
# See http://www.idpf.org/epub/30/spec/epub30-contentdocs.html#sec-xhtml-nav.
128+
# """
129+
# EEx.function_from_file(
130+
# :def,
131+
# :nav_template,
132+
# Path.expand("templates/nav_template.eex", __DIR__),
133+
# [:config, :nodes],
134+
# trim: true
135+
# )
136+
137+
# @doc """
138+
# Creates a new chapter when the user provides additional files.
139+
# """
140+
# EEx.function_from_file(
141+
# :def,
142+
# :extra_template,
143+
# Path.expand("templates/extra_template.eex", __DIR__),
144+
# [:config, :title, :title_content, :content],
145+
# trim: true
146+
# )
147+
148+
149+
# EEx.function_from_file(
150+
# :defp,
151+
# :nav_item_template,
152+
# Path.expand("templates/nav_item_template.eex", __DIR__),
153+
# [:name, :nodes],
154+
# trim: true
155+
# )
156+
157+
# EEx.function_from_file(
158+
# :defp,
159+
# :nav_grouped_item_template,
160+
# Path.expand("templates/nav_grouped_item_template.eex", __DIR__),
161+
# [:nodes],
162+
# trim: true
163+
# )
164+
165+
# EEx.function_from_file(
166+
# :defp,
167+
# :toc_item_template,
168+
# Path.expand("templates/toc_item_template.eex", __DIR__),
169+
# [:nodes],
170+
# trim: true
171+
# )
172+
173+
# "templates/media-types.txt"
174+
# |> Path.expand(__DIR__)
175+
# |> File.read!()
176+
# |> String.split("\n", trim: true)
177+
# |> Enum.each(fn line ->
178+
# [extension, media] = String.split(line, ",")
179+
180+
# def media_type("." <> unquote(extension)) do
181+
# unquote(media)
182+
# end
183+
# end)
184+
185+
# def media_type(_arg), do: nil
186+
187+
templates = [
188+
detail_template: [:node, :module],
189+
summary_template: [:name, :nodes]
190+
]
191+
192+
Enum.each(templates, fn {name, args} ->
193+
filename = Path.expand("templates/#{name}.eex", __DIR__)
194+
@doc false
195+
EEx.function_from_file(:def, name, filename, args, trim: true)
196+
end)
197+
end
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
# <%=h node.signature %>
2+
3+
<%= if node.source_url do %>
4+
[View Source](<%= node.source_url %>)
5+
<% end %>
6+
7+
<%= for annotation <- node.annotations do %>
8+
> (<%= annotation %>)
9+
<% end %>
10+
11+
<%= if deprecated = node.deprecated do %>
12+
> This <%= node.type %> is deprecated. <%= h(deprecated) %>.
13+
<% end %>
14+
15+
<%= if specs = H.get_specs(node) do %>
16+
<%= for spec <- specs do %>
17+
> <%= H.format_spec_attribute(module, node) %> <%= spec %>
18+
<% end %>
19+
<% end %>
20+
21+
<%= link_detail_headings(node_doc(node), H.enc(node.id)) %>

0 commit comments

Comments
 (0)