Skip to content

Commit 6961df5

Browse files
committed
Convert highlight into DocAST
1 parent cbe35b1 commit 6961df5

File tree

3 files changed

+73
-89
lines changed

3 files changed

+73
-89
lines changed

lib/ex_doc/doc_ast.ex

Lines changed: 34 additions & 47 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
import Kernel, except: [to_string: 1]
2+
13
defmodule ExDoc.DocAST do
24
# General helpers for dealing with the documentation AST
35
# (which is the Markdown -> HTML AST).
@@ -198,41 +200,58 @@ defmodule ExDoc.DocAST do
198200
defp pivot([], acc, _headers), do: Enum.reverse(acc)
199201

200202
def highlight(html, language, opts \\ []) do
201-
highlight_info = language.highlight_info()
202-
203-
## Html cannot be parsed with regex, but we try our best...
204-
Regex.replace(
205-
~r/<pre(\s[^>]*)?><code(?:\s+class="([^"\s]*)")?>([^<]*)<\/code><\/pre>/,
206-
html,
207-
&highlight_code_block(&1, &2, &3, &4, highlight_info, opts)
208-
)
203+
do_highlight(html, language.highlight_info(), opts)
209204
end
210205

211-
defp highlight_code_block(full_block, pre_attr, lang, code, highlight_info, outer_opts) do
206+
defp do_highlight(
207+
{:pre, pre_attrs, [{:code, code_attrs, [code], code_meta}], pre_meta} = ast,
208+
highlight_info,
209+
opts
210+
)
211+
when is_binary(code) do
212+
{lang, code_attrs} = Keyword.pop(code_attrs, :class, "")
213+
212214
case pick_language_and_lexer(lang, highlight_info, code) do
213-
{_language, nil, _opts} ->
214-
full_block
215+
{_lang, nil, _lexer_opts} ->
216+
ast
215217

216-
{lang, lexer, opts} ->
218+
{lang, lexer, lexer_opts} ->
217219
try do
218-
render_code(pre_attr, lang, lexer, opts, code, outer_opts)
220+
Makeup.highlight_inner_html(code,
221+
lexer: lexer,
222+
lexer_options: lexer_opts,
223+
formatter_options: opts
224+
)
219225
rescue
220226
exception ->
221227
ExDoc.Utils.warn(
222228
[
223229
"crashed while highlighting #{lang} snippet:\n\n",
224-
full_block,
230+
ExDoc.DocAST.to_string(ast),
225231
"\n\n",
226232
Exception.format_banner(:error, exception, __STACKTRACE__)
227233
],
228234
__STACKTRACE__
229235
)
230236

231-
full_block
237+
ast
238+
else
239+
highlighted ->
240+
code_attrs = [class: "makeup #{lang}", translate: "no"] ++ code_attrs
241+
code_meta = Map.put(code_meta, :verbatim, true)
242+
{:pre, pre_attrs, [{:code, code_attrs, [highlighted], code_meta}], pre_meta}
232243
end
233244
end
234245
end
235246

247+
defp do_highlight(list, highlight_info, opts) when is_list(list) do
248+
Enum.map(list, &do_highlight(&1, highlight_info, opts))
249+
end
250+
251+
defp do_highlight(other, _highlight_info, _opts) do
252+
other
253+
end
254+
236255
defp pick_language_and_lexer("", _highlight_info, "$ " <> _) do
237256
{"shell", ExDoc.ShellLexer, []}
238257
end
@@ -251,36 +270,4 @@ defmodule ExDoc.DocAST do
251270
:error -> {lang, nil, []}
252271
end
253272
end
254-
255-
defp render_code(pre_attr, lang, lexer, lexer_opts, code, opts) do
256-
highlight_tag = Keyword.get(opts, :highlight_tag, "span")
257-
258-
highlighted =
259-
code
260-
|> unescape_html()
261-
|> IO.iodata_to_binary()
262-
|> Makeup.highlight_inner_html(
263-
lexer: lexer,
264-
lexer_options: lexer_opts,
265-
formatter_options: [highlight_tag: highlight_tag]
266-
)
267-
268-
~s(<pre#{pre_attr}><code class="makeup #{lang}" translate="no">#{highlighted}</code></pre>)
269-
end
270-
271-
entities = [{"&amp;", ?&}, {"&lt;", ?<}, {"&gt;", ?>}, {"&quot;", ?"}, {"&#39;", ?'}]
272-
273-
for {encoded, decoded} <- entities do
274-
defp unescape_html(unquote(encoded) <> rest) do
275-
[unquote(decoded) | unescape_html(rest)]
276-
end
277-
end
278-
279-
defp unescape_html(<<c, rest::binary>>) do
280-
[c | unescape_html(rest)]
281-
end
282-
283-
defp unescape_html(<<>>) do
284-
[]
285-
end
286273
end

lib/ex_doc/formatter/html.ex

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,8 +144,8 @@ defmodule ExDoc.Formatter.HTML do
144144
defp autolink_and_render(doc, language, autolink_opts, opts) do
145145
doc
146146
|> language.autolink_doc(autolink_opts)
147-
|> ExDoc.DocAST.to_string()
148147
|> ExDoc.DocAST.highlight(language, opts)
148+
|> ExDoc.DocAST.to_string()
149149
end
150150

151151
defp output_setup(build, config) do

test/ex_doc/doc_ast_test.exs

Lines changed: 38 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -158,54 +158,51 @@ defmodule ExDoc.DocASTTest do
158158

159159
describe "highlight" do
160160
test "with default class" do
161-
# Empty class
162-
assert DocAST.highlight(
163-
~S[<pre><code class="">mix run --no-halt path/to/file.exs</code></pre>],
164-
ExDoc.Language.Elixir
165-
) =~
161+
# Four spaces
162+
assert highlight("""
163+
mix run --no-halt path/to/file.exs
164+
""") =~
166165
~r{<pre><code class=\"makeup elixir\" translate="no">.*}
167166

168-
# Without class
169-
assert DocAST.highlight(
170-
"<pre><code>mix run --no-halt path/to/file.exs</code></pre>",
171-
ExDoc.Language.Elixir
172-
) =~
167+
# Code block without language
168+
assert highlight("""
169+
```
170+
mix run --no-halt path/to/file.exs</code></pre>
171+
```
172+
""") =~
173173
~r{<pre><code class=\"makeup elixir\" translate="no">.*}
174174

175-
# Pre class
176-
assert DocAST.highlight(
177-
~S[<pre class="wrap"><code class="">mix run --no-halt path/to/file.exs</code></pre>],
178-
ExDoc.Language.Elixir
179-
) =~
175+
# Pre IAL
176+
assert highlight("""
177+
```
178+
mix run --no-halt path/to/file.exs</code></pre>
179+
```
180+
{:class="wrap"}
181+
""") =~
180182
~r{<pre class="wrap"><code class=\"makeup elixir\" translate="no">.*}
181183

182-
# Pre id
183-
assert DocAST.highlight(
184-
~S[<pre id="anchor"><code class="">mix run --no-halt path/to/file.exs</code></pre>],
185-
ExDoc.Language.Elixir
186-
) =~
187-
~r{<pre id="anchor"><code class=\"makeup elixir\" translate="no">.*}
188-
189-
# Pre id and class
190-
assert DocAST.highlight(
191-
~S[<pre id="anchor" class="wrap"><code class="">mix run --no-halt path/to/file.exs</code></pre>],
192-
ExDoc.Language.Elixir
193-
) =~
194-
~r{<pre id="anchor" class="wrap"><code class=\"makeup elixir\" translate="no">.*}
195-
196-
# IEx highlight with empty class
197-
assert DocAST.highlight(
198-
~S[<pre><code class="">iex&gt; max(4, 5)</code></pre>],
199-
ExDoc.Language.Elixir
200-
) =~
201-
~r{<pre><code class=\"makeup elixir\" translate="no">.*}
184+
# Code with language
185+
assert highlight("""
186+
```html
187+
<foo />
188+
```
189+
""") =~
190+
~r{<pre><code class=\"makeup html\" translate="no">.*}
191+
192+
# Code with shell detection
193+
assert highlight("""
194+
```
195+
$ hello
196+
```
197+
""") =~
198+
~r{<pre><code class=\"makeup shell\" translate="no"><span class="gp unselectable">\$.*}
199+
end
202200

203-
# IEx highlight without class
204-
assert DocAST.highlight(
205-
~S[<pre><code>iex&gt; max(4, 5)</code></pre>],
206-
ExDoc.Language.Elixir
207-
) =~
208-
~r{<pre><code class=\"makeup elixir\" translate="no">.*}
201+
defp highlight(markdown) do
202+
markdown
203+
|> ExDoc.DocAST.parse!("text/markdown")
204+
|> ExDoc.DocAST.highlight(ExDoc.Language.Elixir)
205+
|> ExDoc.DocAST.to_string()
209206
end
210207
end
211208

0 commit comments

Comments
 (0)