Skip to content

Commit 603afc5

Browse files
committed
Consistent search data rendering
1 parent 6224691 commit 603afc5

File tree

8 files changed

+67
-128
lines changed

8 files changed

+67
-128
lines changed

lib/ex_doc/doc_ast.ex

Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -183,16 +183,21 @@ defmodule ExDoc.DocAST do
183183
@doc """
184184
Returns text content from the given AST.
185185
"""
186-
def text(ast) do
186+
def text(ast, joiner \\ "") do
187187
ast
188-
|> do_text()
188+
|> do_text(joiner)
189189
|> IO.iodata_to_binary()
190190
|> String.trim()
191191
end
192192

193-
defp do_text(ast) when is_list(ast), do: Enum.map(ast, &do_text/1)
194-
defp do_text(ast) when is_binary(ast), do: ast
195-
defp do_text({_tag, _attr, ast, _meta}), do: text(ast)
193+
defp do_text(ast, joiner) when is_list(ast),
194+
do: Enum.map_intersperse(ast, joiner, &do_text(&1, joiner))
195+
196+
defp do_text(ast, _joiner) when is_binary(ast),
197+
do: ast
198+
199+
defp do_text({_tag, _attr, ast, _meta}, joiner),
200+
do: do_text(ast, joiner)
196201

197202
@doc """
198203
Wraps a list of HTML nodes into `<section>` tags whenever `headers` returns true.

lib/ex_doc/formatter/html.ex

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ defmodule ExDoc.Formatter.HTML do
2222
project_nodes = render_all(project_nodes, filtered_modules, ".html", config, [])
2323
extras = build_extras(config, ".html")
2424

25-
# Generate search early on without api reference in extras
2625
static_files = generate_assets(".", default_assets(config), config)
2726
search_data = generate_search_data(project_nodes, extras, config)
2827

@@ -62,6 +61,7 @@ defmodule ExDoc.Formatter.HTML do
6261
@doc """
6362
Autolinks and renders all docs.
6463
"""
64+
# TODO: Move this outside of the formatter
6565
def render_all(project_nodes, filtered_modules, ext, config, opts) do
6666
base = [
6767
apps: config.apps,
@@ -120,7 +120,7 @@ defmodule ExDoc.Formatter.HTML do
120120

121121
defp render_doc(%{doc: doc} = node, language, autolink_opts, opts) do
122122
doc = autolink_and_highlight(doc, language, autolink_opts, opts)
123-
%{node | doc: doc, rendered_doc: ExDoc.DocAST.to_string(doc)}
123+
%{node | doc: doc}
124124
end
125125

126126
defp id(%{id: mod_id}, %{id: "c:" <> id}) do

lib/ex_doc/formatter/html/search_data.ex

Lines changed: 50 additions & 106 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
defmodule ExDoc.Formatter.HTML.SearchData do
22
@moduledoc false
3-
alias ExDoc.Utils
43

54
def create(nodes, extras, proglang) do
65
items = Enum.flat_map(nodes, &module/1) ++ Enum.flat_map(extras, &extra/1)
@@ -24,147 +23,92 @@ defmodule ExDoc.Formatter.HTML.SearchData do
2423
Enum.map(search_data, fn item ->
2524
link =
2625
if item.anchor === "" do
27-
"#{map.id}.html"
26+
"#{URI.encode(map.id)}.html"
2827
else
29-
"#{map.id}.html##{item.anchor}"
28+
"#{URI.encode(map.id)}.html##{URI.encode(item.anchor)}"
3029
end
3130

3231
encode(link, item.title <> " - #{map.id}", item.type, clean_markdown(item.body))
3332
end)
3433
end
3534

3635
defp extra(map) do
37-
{intro, sections} = extract_sections_from_markdown(map.source)
38-
39-
intro_json_item =
40-
encode(
41-
"#{map.id}.html",
42-
map.title,
43-
:extras,
44-
intro
45-
)
46-
47-
section_json_items =
48-
for {header, body} <- sections do
49-
encode(
50-
"#{map.id}.html##{Utils.text_to_id(header)}",
51-
header <> " - #{map.title}",
52-
:extras,
53-
body
54-
)
55-
end
56-
57-
[intro_json_item | section_json_items]
36+
page = URI.encode(map.id) <> ".html"
37+
{intro, sections} = extract_sections_from_markdown(map.source, "")
38+
39+
intro = encode(page, map.title, :extras, intro)
40+
[intro | render_sections(sections, page, map.title, :extras)]
5841
end
5942

6043
defp module(%ExDoc.ModuleNode{} = node) do
61-
# TODO: This should work on DocAST
62-
{intro, sections} = extract_sections(node.doc_format, node)
63-
64-
module =
65-
encode(
66-
"#{node.id}.html",
67-
node.title,
68-
node.type,
69-
intro
70-
)
71-
72-
module_sections =
73-
for {header, body} <- sections do
74-
encode(
75-
"#{node.id}.html#module-#{Utils.text_to_id(header)}",
76-
header <> " - #{node.title}",
77-
node.type,
78-
body
79-
)
80-
end
81-
82-
docs = Enum.flat_map(node.docs, &node_child(&1, node))
83-
[module] ++ module_sections ++ docs
44+
page = URI.encode(node.id) <> ".html"
45+
{intro, sections} = extract_sections(node.source_format, node, "module-")
46+
module = encode(page, node.title, node.type, intro)
47+
docs = Enum.flat_map(node.docs, &node_child(&1, node, page))
48+
[module] ++ render_sections(sections, page, node.title, node.type) ++ docs
8449
end
8550

86-
defp node_child(node, module_node) do
87-
{intro, sections} = extract_sections(module_node.doc_format, node)
88-
89-
child =
90-
encode(
91-
"#{module_node.id}.html##{node.id}",
92-
"#{module_node.id}.#{node.name}/#{node.arity}",
93-
node.type,
94-
intro
95-
)
96-
97-
child_sections =
98-
for {header, body} <- sections do
99-
encode(
100-
"#{module_node.id}.html##{node.id}-#{Utils.text_to_id(header)}",
101-
header <> " - #{module_node.id}.#{node.name}/#{node.arity}",
102-
node.type,
103-
body
104-
)
105-
end
106-
107-
[child] ++ child_sections
51+
defp node_child(node, module_node, page) do
52+
title = "#{module_node.id}.#{node.name}/#{node.arity}"
53+
{intro, sections} = extract_sections(module_node.source_format, node, node.id <> "-")
54+
55+
child = encode("#{page}##{URI.encode(node.id)}", title, node.type, intro)
56+
[child | render_sections(sections, page, title, node.type)]
10857
end
10958

11059
defp encode(ref, title, type, doc) do
111-
%{
112-
ref: URI.encode(ref),
113-
title: title,
114-
type: type,
115-
doc: doc
116-
}
60+
%{ref: ref, title: title, type: type, doc: doc}
11761
end
11862

119-
# TODO: Perform this via DocAST and remove doc_format (and perhaps source_doc)
120-
defp extract_sections("text/markdown", %{source_doc: %{"en" => doc}}) do
121-
extract_sections_from_markdown(doc)
63+
# TODO: Perform this via DocAST and remove source_format (and perhaps source_doc)
64+
defp extract_sections("text/markdown", %{source_doc: %{"en" => doc}}, prefix) do
65+
extract_sections_from_markdown(doc, prefix)
12266
end
12367

124-
defp extract_sections("application/erlang+html", %{rendered_doc: nil}) do
125-
{nil, []}
68+
defp extract_sections(_format, %{doc: nil}, _prefix) do
69+
{"", []}
12670
end
12771

128-
defp extract_sections("application/erlang+html", %{rendered_doc: doc}) do
129-
{clean_html(doc), []}
72+
defp extract_sections(_format, %{doc: doc}, _prefix) do
73+
{ExDoc.DocAST.text(doc, " "), []}
13074
end
13175

132-
defp extract_sections(_format, _doc) do
133-
{"", []}
134-
end
135-
136-
# TODO: This should work on DocAST when we prebuild extra.
137-
defp extract_sections_from_markdown(string) do
138-
[intro | sections] =
76+
defp extract_sections_from_markdown(string, prefix) do
77+
[intro | headers_sections] =
13978
Regex.split(~r/(?<!#)###? (?<header>\b.+)/, string, include_captures: true)
14079

141-
sections =
142-
for [header, section] <- Enum.chunk_every(sections, 2) do
143-
header = String.trim_leading(header, "#")
80+
{headers, sections} =
81+
headers_sections
82+
|> Enum.chunk_every(2)
83+
|> Enum.map(fn [header, section] -> {header, section} end)
84+
|> Enum.unzip()
14485

145-
section =
146-
section
147-
|> ExDoc.Utils.strip_tags(" ")
148-
|> drop_ignorable_codeblocks()
149-
|> String.trim()
86+
# Now convert the headers into a single markdown document
87+
header_tags =
88+
headers
89+
|> Enum.join("\n\n")
90+
|> ExDoc.Markdown.to_ast()
91+
|> ExDoc.DocAST.add_ids_to_headers([:h2, :h3], prefix)
15092

151-
{clean_markdown(header), section}
152-
end
93+
sections =
94+
Enum.zip_with(header_tags, sections, fn {_, attrs, inner, _}, section ->
95+
{ExDoc.DocAST.text(inner), Keyword.fetch!(attrs, :id), clean_markdown(section)}
96+
end)
15397

15498
{clean_markdown(intro), sections}
15599
end
156100

157-
defp clean_markdown(doc) do
158-
doc
101+
defp clean_markdown(text) do
102+
text
159103
|> ExDoc.Utils.strip_tags(" ")
104+
|> drop_ignorable_codeblocks()
160105
|> String.trim()
161106
end
162107

163-
defp clean_html(doc) do
164-
doc
165-
|> ExDoc.Utils.strip_tags(" ")
166-
|> String.replace(~r/\s+/, " ")
167-
|> String.trim()
108+
defp render_sections(sections, page, title, type) do
109+
for {header, anchor, body} <- sections do
110+
encode("#{page}##{anchor}", header <> " - " <> title, type, body)
111+
end
168112
end
169113

170114
@ignored_codeblocks ~w[vega-lite]

lib/ex_doc/nodes.ex

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,9 @@ defmodule ExDoc.ModuleNode do
99
module: nil,
1010
group: nil,
1111
deprecated: nil,
12-
doc_format: nil,
1312
doc: nil,
1413
source_doc: nil,
15-
rendered_doc: nil,
14+
source_format: nil,
1615
moduledoc_line: nil,
1716
moduledoc_file: nil,
1817
source_path: nil,
@@ -35,10 +34,9 @@ defmodule ExDoc.ModuleNode do
3534
module: module(),
3635
group: atom() | nil,
3736
deprecated: String.t() | nil,
38-
doc_format: String.t() | nil,
3937
doc: ExDoc.DocAST.t() | nil,
4038
source_doc: term() | nil,
41-
rendered_doc: String.t() | nil,
39+
source_format: String.t() | nil,
4240
moduledoc_line: non_neg_integer(),
4341
moduledoc_file: String.t(),
4442
source_path: String.t() | nil,
@@ -63,7 +61,6 @@ defmodule ExDoc.DocNode do
6361
deprecated: nil,
6462
doc: nil,
6563
source_doc: nil,
66-
rendered_doc: nil,
6764
type: nil,
6865
signature: nil,
6966
specs: [],
@@ -84,7 +81,6 @@ defmodule ExDoc.DocNode do
8481
deprecated: String.t() | nil,
8582
doc: ExDoc.DocAST.t() | nil,
8683
source_doc: term() | nil,
87-
rendered_doc: String.t() | nil,
8884
type: atom(),
8985
signature: String.t(),
9086
specs: [ExDoc.Language.spec_ast()],

lib/ex_doc/retriever.ex

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -157,9 +157,9 @@ defmodule ExDoc.Retriever do
157157
deprecated: metadata[:deprecated],
158158
docs_groups: config.docs_groups ++ module_data.default_groups,
159159
docs: ExDoc.Utils.natural_sort_by(docs, &"#{&1.name}/#{&1.arity}"),
160-
doc_format: format,
161160
doc: normalize_doc_ast(doc_ast, "module-"),
162161
source_doc: source_doc,
162+
source_format: format,
163163
moduledoc_line: doc_line,
164164
moduledoc_file: doc_file,
165165
source_url: source_link(source, module_data.source_line),

test/ex_doc/formatter/html/search_data_test.exs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,7 @@ defmodule ExDoc.Formatter.HTML.SearchDataTest do
112112
erlc(c, :search_foo, """
113113
%% @doc
114114
%% Hello <em>world</em>.
115+
%% Newline.
115116
-module(search_foo).
116117
""")
117118

@@ -122,7 +123,7 @@ defmodule ExDoc.Formatter.HTML.SearchDataTest do
122123
assert item["ref"] == "search_foo.html"
123124
assert item["type"] == "module"
124125
assert item["title"] == "search_foo"
125-
assert item["doc"] == "Hello world ."
126+
assert item["doc"] == "Hello world . Newline."
126127
end
127128

128129
test "function", c do

test/ex_doc/retriever/elixir_test.exs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,6 @@ defmodule ExDoc.Retriever.ElixirTest do
5151
group: "Functions",
5252
id: "function/0",
5353
name: :function,
54-
rendered_doc: nil,
5554
signature: "function()",
5655
source_url: nil,
5756
specs: [spec],

test/ex_doc/retriever/erlang_test.exs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,6 @@ defmodule ExDoc.Retriever.ErlangTest do
6666
module: :mod,
6767
nested_context: nil,
6868
nested_title: nil,
69-
rendered_doc: nil,
7069
source_path: _,
7170
source_url: _,
7271
title: "mod",
@@ -87,7 +86,6 @@ defmodule ExDoc.Retriever.ErlangTest do
8786
group: "Functions",
8887
id: "function1/0",
8988
name: :function1,
90-
rendered_doc: nil,
9189
signature: _,
9290
source_url: _,
9391
specs: _,
@@ -163,7 +161,6 @@ defmodule ExDoc.Retriever.ErlangTest do
163161
module: :mod,
164162
nested_context: nil,
165163
nested_title: nil,
166-
rendered_doc: nil,
167164
source_path: _,
168165
source_url: "module.hrl:2",
169166
title: "mod",
@@ -183,7 +180,6 @@ defmodule ExDoc.Retriever.ErlangTest do
183180
group: "Functions",
184181
id: "function/0",
185182
name: :function,
186-
rendered_doc: nil,
187183
signature: _,
188184
source_url: "function.hrl:24",
189185
specs: _,
@@ -404,7 +400,6 @@ defmodule ExDoc.Retriever.ErlangTest do
404400
module: :mod,
405401
nested_context: nil,
406402
nested_title: nil,
407-
rendered_doc: nil,
408403
source_path: _,
409404
source_url: _,
410405
title: "mod",
@@ -424,7 +419,6 @@ defmodule ExDoc.Retriever.ErlangTest do
424419
group: "Functions",
425420
id: "function1/0",
426421
name: :function1,
427-
rendered_doc: nil,
428422
signature: _,
429423
source_url: _,
430424
specs: _,

0 commit comments

Comments
 (0)