From 414359cb360cb18973a27a867156bc20271f4b70 Mon Sep 17 00:00:00 2001 From: Eksperimental Date: Sun, 21 Jun 2020 14:37:39 -0500 Subject: [PATCH] Introduce Markdown.AST - Introduce ExDoc.Markdown.AST and t:Markdown.AST.html/0. - Replaces ExDoc.Formatter.HTML.ast_to_html/1 with ExDoc.Markdown.AST.to_html/2 which is a port of Earmark.Transform - It uses a more recent git version of Earkmark since due to a bug in the library. - It adds Floki to deal with HTML code in Markdown docs. Closes #1168, #1189 Supersedes #1190 --- lib/ex_doc/autolink.ex | 18 +- lib/ex_doc/formatter/html.ex | 14 +- lib/ex_doc/markdown/ast.ex | 161 ++++++++++++++++++ lib/ex_doc/markdown/earmark.ex | 113 +++++++++--- lib/ex_doc/retriever.ex | 3 +- mix.exs | 5 +- mix.lock | 4 +- test/ex_doc/autolink_test.exs | 8 +- test/ex_doc/formatter/html/templates_test.exs | 11 +- test/ex_doc/formatter/html_test.exs | 24 +++ test/ex_doc/markdown/earmark_test.exs | 17 +- test/ex_doc/retriever_test.exs | 40 +++-- test/fixtures/ExtraPageWithHTML.md | 62 +++++++ test/fixtures/compiled_with_docs.ex | 2 +- 14 files changed, 407 insertions(+), 75 deletions(-) create mode 100644 lib/ex_doc/markdown/ast.ex create mode 100644 test/fixtures/ExtraPageWithHTML.md diff --git a/lib/ex_doc/autolink.ex b/lib/ex_doc/autolink.ex index 927c62699..26188f90b 100644 --- a/lib/ex_doc/autolink.ex +++ b/lib/ex_doc/autolink.ex @@ -48,7 +48,7 @@ defmodule ExDoc.Autolink do @autoimported_modules [Kernel, Kernel.SpecialForms] - def doc(ast, options \\ []) do + def doc(ast, options) do config = struct!(__MODULE__, options) walk(ast, config) end @@ -61,34 +61,34 @@ defmodule ExDoc.Autolink do binary end - defp walk({:pre, _, _} = ast, _config) do + defp walk({:pre, _metadata, _, _} = ast, _config) do ast end - defp walk({:a, attrs, inner} = ast, config) do + defp walk({:a, metadata, attrs, inner} = ast, config) do cond do url = custom_link(attrs, config) -> - {:a, Keyword.put(attrs, :href, url), inner} + {:a, metadata, Keyword.put(attrs, :href, url), inner} url = extra_link(attrs, config) -> - {:a, Keyword.put(attrs, :href, url), inner} + {:a, metadata, Keyword.put(attrs, :href, url), inner} true -> ast end end - defp walk({:code, attrs, [code]} = ast, config) do + defp walk({:code, metadata, attrs, [code]} = ast, config) do if url = url(code, :regular, config) do code = remove_prefix(code) - {:a, [href: url], [{:code, attrs, [code]}]} + {:a, metadata, [href: url], [{:code, metadata, attrs, [code]}]} else ast end end - defp walk({tag, attrs, ast}, config) do - {tag, attrs, walk(ast, config)} + defp walk({tag, metadata, attrs, ast}, config) do + {tag, metadata, attrs, walk(ast, config)} end defp custom_link(attrs, config) do diff --git a/lib/ex_doc/formatter/html.ex b/lib/ex_doc/formatter/html.ex index 1f4e7bfe2..49dfecbea 100644 --- a/lib/ex_doc/formatter/html.ex +++ b/lib/ex_doc/formatter/html.ex @@ -1,6 +1,8 @@ defmodule ExDoc.Formatter.HTML do @moduledoc false + alias ExDoc.Markdown.AST + alias __MODULE__.{Assets, Templates, SearchItems} alias ExDoc.{Autolink, Markdown, GroupMatcher} @@ -117,20 +119,10 @@ defmodule ExDoc.Formatter.HTML do defp autolink_and_render(doc, autolink_opts, opts) do doc |> Autolink.doc(autolink_opts) - |> ast_to_html() - |> IO.iodata_to_binary() + |> AST.to_html() |> ExDoc.Highlighter.highlight_code_blocks(opts) end - @doc false - def ast_to_html(list) when is_list(list), do: Enum.map(list, &ast_to_html/1) - def ast_to_html(binary) when is_binary(binary), do: Templates.h(binary) - - def ast_to_html({tag, attrs, ast}) do - attrs = Enum.map(attrs, fn {key, val} -> " #{key}=\"#{val}\"" end) - ["<#{tag}", attrs, ">", ast_to_html(ast), ""] - end - defp output_setup(build, config) do if File.exists?(build) do build diff --git a/lib/ex_doc/markdown/ast.ex b/lib/ex_doc/markdown/ast.ex new file mode 100644 index 000000000..7921ee41b --- /dev/null +++ b/lib/ex_doc/markdown/ast.ex @@ -0,0 +1,161 @@ +defmodule ExDoc.Markdown.AST do + @type html :: [html_element()] + + @type html_element :: {html_tag(), metadata(), html_attributes(), children()} | String.t() + @type html_tag :: atom() + @type metadata :: %{ + optional(atom()) => any(), + optional(:line) => integer(), + optional(:column) => integer(), + optional(:verbatim) => boolean(), + optional(:comment) => boolean() + } + @type html_attributes :: Keyword.t(String.t()) + @type children :: ast() + + # https://www.w3.org/TR/2011/WD-html-markup-20110113/syntax.html#void-element + @void_elements ~W(area base br col command embed hr img input keygen link meta param source track wbr)a + + # Ported from: Earmark.Transform + # Copyright (c) 2014 Dave Thomas, The Pragmatic Programmers @/+pragdave, dave@pragprog.com + # Apache License v2.0 + # https://github.com/pragdave/earmark/blob/a2a85bc3f2e262a2c697ed8001b0eaa06ee42d92/lib/earmark/transform.ex + @spec to_html(html()) :: String.t() + def to_html(ast, options \\ %{}) + + def to_html(ast, options) do + ast + |> to_html(options, false) + |> IO.iodata_to_binary() + end + + defp to_html(elements, options, verbatim) when is_list(elements) do + Enum.map(elements, &to_html(&1, options, verbatim)) + end + + defp to_html(element, options, false) when is_binary(element) do + case escape_with_options(element, options) do + "" -> + [] + + content -> + [content] + end + end + + defp to_html(element, _options, true) when is_binary(element) do + [element] + end + + # Void element + defp to_html({tag, _metadata, attributes, []}, _options, _verbatim) when tag in @void_elements, + do: open_element(tag, attributes) + + # Comment + defp to_html({nil, %{comment: true}, _attributes, children}, _options, _verbatim) do + [""] + end + + defp to_html({:code, _metadata, attributes, children}, _options, __verbatim) do + [ + open_element(:code, attributes), + children |> Enum.join("\n") |> escape(true), + "" + ] + end + + defp to_html({:pre, metadata, attributes, children}, options, verbatim) do + verbatim_new = metadata[:verbatim] || verbatim + + [ + open_element(:pre, attributes), + to_html(Enum.intersperse(children, ["\n"]), options, verbatim_new), + "\n" + ] + end + + # Element with no children + defp to_html({tag, _metadata, attributes, []}, _options, _verbatim) do + [open_element(tag, attributes), "", "\n"] + end + + # Element with children + defp to_html({tag, metadata, attributes, children}, options, verbatim) do + verbatim_new = metadata[:verbatim] || verbatim + + [open_element(tag, attributes), to_html(children, options, verbatim_new), ""] + end + + defp make_attribute(name_value_pair, tag) + + defp make_attribute({name, value}, _) do + [" ", "#{name}", "=\"", to_string(value), "\""] + end + + defp open_element(tag, attributes) when tag in @void_elements do + ["<", "#{tag}", Enum.map(attributes, &make_attribute(&1, tag)), " />"] + end + + defp open_element(tag, attributes) do + ["<", "#{tag}", Enum.map(attributes, &make_attribute(&1, tag)), ">"] + end + + @em_dash_regex ~r{---} + @en_dash_regex ~r{--} + @dbl1_regex ~r{(^|[-–—/\(\[\{"”“\s])'} + @single_regex ~r{\'} + @dbl2_regex ~r{(^|[-–—/\(\[\{‘\s])\"} + @dbl3_regex ~r{"} + defp smartypants(text, options) + + defp smartypants(text, %{smartypants: true}) do + text + |> replace(@em_dash_regex, "—") + |> replace(@en_dash_regex, "–") + |> replace(@dbl1_regex, "\\1‘") + |> replace(@single_regex, "’") + |> replace(@dbl2_regex, "\\1“") + |> replace(@dbl3_regex, "”") + |> String.replace("...", "…") + end + + defp smartypants(text, _options), do: text + + defp replace(text, regex, replacement, options \\ []) do + Regex.replace(regex, text, replacement, options) + end + + # Originally taken from: Earmark.Helpers + # Copyright (c) 2014 Dave Thomas, The Pragmatic Programmers @/+pragdave, dave@pragprog.com + # Apache License v2.0 + # https://github.com/pragdave/earmark/blob/a2a85bc3f2e262a2c697ed8001b0eaa06ee42d92/lib/earmark/helpers.ex + # + # Replace <, >, and quotes with the corresponding entities. If + # `encode` is true, convert ampersands, too, otherwise only + # convert non-entity ampersands. + def escape(html, encode \\ false) + + def escape(html, false) when is_binary(html), + do: escape_replace(Regex.replace(~r{&(?!#?\w+;)}, html, "&")) + + def escape(html, _) when is_binary(html), do: escape_replace(String.replace(html, "&", "&")) + + defp escape_replace(html) do + html + |> String.replace("<", "<") + |> String.replace(">", ">") + |> String.replace("\"", """) + |> String.replace("'", "'") + end + + defp escape_with_options(element, options) + + defp escape_with_options("", _options), + do: "" + + defp escape_with_options(element, options) do + element + |> smartypants(options) + |> escape() + end +end diff --git a/lib/ex_doc/markdown/earmark.ex b/lib/ex_doc/markdown/earmark.ex index 1cf93ab61..0c491fc4d 100644 --- a/lib/ex_doc/markdown/earmark.ex +++ b/lib/ex_doc/markdown/earmark.ex @@ -26,7 +26,7 @@ defmodule ExDoc.Markdown.Earmark do """ @impl true - def to_ast(text, opts) do + def to_ast(text, opts) when is_binary(text) do options = struct(Earmark.Options, gfm: Keyword.get(opts, :gfm, true), @@ -37,13 +37,33 @@ defmodule ExDoc.Markdown.Earmark do pure_links: true ) - case Earmark.as_ast(text, options) do - {:ok, ast, messages} -> - print_messages(messages, options) - fixup(ast) + as_ast(text, options) + end + + defp as_ast(binary, options, meta \\ %{}) do + {response, ast, messages} = Earmark.as_ast(binary, options) + print_messages(messages, options) + + verbatim = meta[:verbatim] || false + + case response do + :ok when verbatim and is_tuple(ast) -> + case ast do + {tag, attrs, children, ast_meta} -> + fixup( + {tag, attrs, children, Kernel.put_in(ast_meta, :verbatim, true)}, + options, + meta + ) + + {tag, attrs, children} -> + fixup({tag, attrs, children, %{meta: %{verbatim: true}}}, options, meta) + end - {:error, ast, messages} -> - print_messages(messages, options) + :ok -> + fixup(ast, options, meta) + + :error -> ast end end @@ -55,38 +75,58 @@ defmodule ExDoc.Markdown.Earmark do end end - defp fixup(list) when is_list(list) do - fixup_list(list, []) + defp fixup(list, options, meta) when is_list(list) do + fixup_list(list, [], options, meta) + end + + defp fixup(binary, options, %{verbatim: true} = meta) when is_binary(binary) do + case Floki.parse_document(binary) do + {:ok, [head]} when is_binary(head) -> + head + + {:ok, ast_floki} -> + fixup(ast_floki, options, meta) + end end - defp fixup(binary) when is_binary(binary) do + defp fixup(binary, _options, _meta) when is_binary(binary) do binary end - defp fixup({tag, attrs, ast}) when is_binary(tag) do - {fixup_tag(tag), Enum.map(attrs, &fixup_attr/1), fixup(ast)} + defp fixup({tag, attrs, ast, ast_meta}, options, meta) when is_binary(tag) do + verbatim = meta[:verbatim] || ast_meta[:meta][:verbatim] || false + + { + fixup_tag(tag), + fixup_meta(ast_meta), + Enum.map(attrs, &fixup_attr/1), + fixup( + ast, + options, + Map.put(meta, :verbatim, verbatim) + ) + } end - defp fixup({tag, attrs, ast, _meta}) when is_binary(tag) do - fixup({tag, attrs, ast}) + defp fixup({tag, attrs, ast}, options, meta) when is_binary(tag) do + fixup({tag, attrs, ast, %{}}, options, meta) end - # E.g. `{:comment, _}` - defp fixup(_) do - [] + defp fixup({:comment, children}, _options, meta) do + {nil, Map.put(meta, :comment, true), [], children} end - defp fixup_list([head | tail], acc) do - fixed = fixup(head) + defp fixup_list([head | tail], acc, options, meta) do + case fixup(head, options, meta) do + [] -> + fixup_list(tail, acc, options, meta) - if fixed == [] do - fixup_list(tail, acc) - else - fixup_list(tail, [fixed | acc]) + fixed -> + fixup_list(tail, [fixed | acc], options, meta) end end - defp fixup_list([], acc) do + defp fixup_list([], acc, _options, _meta) do Enum.reverse(acc) end @@ -95,6 +135,29 @@ defmodule ExDoc.Markdown.Earmark do end defp fixup_attr({name, value}) do - {String.to_atom(name), value} + {String.to_atom(name), to_string(value)} + end + + defp fixup_meta(meta) do + fixup_meta(meta, %{}) end + + defp fixup_meta(%{line_number: line_number} = meta, acc), + do: fixup_meta(Map.delete(meta, :line_number), Map.put(acc, :line_number, line_number)) + + defp fixup_meta(%{lnb: line_number} = meta, acc), + do: fixup_meta(Map.delete(meta, :lnb), Map.put(acc, :line_number, line_number)) + + defp fixup_meta(%{meta: %{verbatim: verbatim}} = meta, acc), + # Delete the whole meta, since it only holds :verbatim + do: fixup_meta(Map.delete(meta, :meta), Map.put(acc, :verbatim, verbatim)) + + defp fixup_meta(%{verbatim: verbatim} = meta, acc), + do: fixup_meta(Map.delete(meta, :verbatim), Map.put(acc, :verbatim, verbatim)) + + defp fixup_meta(%{comment: comment} = meta, acc), + do: fixup_meta(Map.delete(meta, :comment), Map.put(acc, :comment, comment)) + + defp fixup_meta(meta, acc), + do: Map.merge(meta, acc) end diff --git a/lib/ex_doc/retriever.ex b/lib/ex_doc/retriever.ex index 6cd966e68..909f42bbe 100644 --- a/lib/ex_doc/retriever.ex +++ b/lib/ex_doc/retriever.ex @@ -327,7 +327,8 @@ defmodule ExDoc.Retriever do defp delegate_doc(nil), do: nil defp delegate_doc({m, f, a}), - do: [{:p, [], ["See ", {:code, [], [Exception.format_mfa(m, f, a)]}, "."]}] + # TODO: Add metadata once we introduce :line and :column + do: [{:p, %{}, [], ["See ", {:code, %{}, [], [Exception.format_mfa(m, f, a)]}, "."]}] defp docstring(:none, name, arity, {:ok, behaviour}) do "Callback implementation for `c:#{inspect(behaviour)}.#{name}/#{arity}`." diff --git a/mix.exs b/mix.exs index 3f286c17a..0f4637e85 100644 --- a/mix.exs +++ b/mix.exs @@ -30,8 +30,11 @@ defmodule ExDoc.Mixfile do defp deps do [ - {:earmark, "~> 1.4.0"}, + {:earmark, + git: "https://github.com/pragdave/earmark.git", + ref: "ecc9b71040c9fbeb5300b2c4cca4650c5a0254a7"}, {:makeup_elixir, "~> 0.14"}, + {:floki, "~> 0.26.0"}, {:excoveralls, "~> 0.3", only: :test}, {:jason, "~> 1.2", only: :test} ] diff --git a/mix.lock b/mix.lock index ad1888b6d..94d922d02 100644 --- a/mix.lock +++ b/mix.lock @@ -1,8 +1,10 @@ %{ "certifi": {:hex, :certifi, "2.5.1", "867ce347f7c7d78563450a18a6a28a8090331e77fa02380b4a21962a65d36ee5", [:rebar3], [{:parse_trans, "~>3.3", [hex: :parse_trans, repo: "hexpm", optional: false]}], "hexpm", "805abd97539caf89ec6d4732c91e62ba9da0cda51ac462380bbd28ee697a8c42"}, - "earmark": {:hex, :earmark, "1.4.5", "62ffd3bd7722fb7a7b1ecd2419ea0b458c356e7168c1f5d65caf09b4fbdd13c8", [:mix], [], "hexpm", "b7d0e6263d83dc27141a523467799a685965bf8b13b6743413f19a7079843f4f"}, + "earmark": {:git, "https://github.com/pragdave/earmark.git", "ecc9b71040c9fbeb5300b2c4cca4650c5a0254a7", [ref: "ecc9b71040c9fbeb5300b2c4cca4650c5a0254a7"]}, "excoveralls": {:hex, :excoveralls, "0.11.1", "dd677fbdd49114fdbdbf445540ec735808250d56b011077798316505064edb2c", [:mix], [{:hackney, "~> 1.0", [hex: :hackney, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "493daf5a2dd92d022a1c29e7edcc30f1bce1ffe10fb3690fac63889346d3af2f"}, + "floki": {:hex, :floki, "0.26.0", "4df88977e2e357c6720e1b650f613444bfb48c5acfc6a0c646ab007d08ad13bf", [:mix], [{:html_entities, "~> 0.5.0", [hex: :html_entities, repo: "hexpm", optional: false]}], "hexpm", "e7b66ce7feef5518a9cd9fc7b52dd62a64028bd9cb6d6ad282a0f0fc90a4ae52"}, "hackney": {:hex, :hackney, "1.15.1", "9f8f471c844b8ce395f7b6d8398139e26ddca9ebc171a8b91342ee15a19963f4", [:rebar3], [{:certifi, "2.5.1", [hex: :certifi, repo: "hexpm", optional: false]}, {:idna, "6.0.0", [hex: :idna, repo: "hexpm", optional: false]}, {:metrics, "1.0.1", [hex: :metrics, repo: "hexpm", optional: false]}, {:mimerl, "~>1.1", [hex: :mimerl, repo: "hexpm", optional: false]}, {:ssl_verify_fun, "1.1.4", [hex: :ssl_verify_fun, repo: "hexpm", optional: false]}], "hexpm", "c2790c9f0f7205f4a362512192dee8179097394400e745e4d20bab7226a8eaad"}, + "html_entities": {:hex, :html_entities, "0.5.1", "1c9715058b42c35a2ab65edc5b36d0ea66dd083767bef6e3edb57870ef556549", [:mix], [], "hexpm", "30efab070904eb897ff05cd52fa61c1025d7f8ef3a9ca250bc4e6513d16c32de"}, "idna": {:hex, :idna, "6.0.0", "689c46cbcdf3524c44d5f3dde8001f364cd7608a99556d8fbd8239a5798d4c10", [:rebar3], [{:unicode_util_compat, "0.4.1", [hex: :unicode_util_compat, repo: "hexpm", optional: false]}], "hexpm", "4bdd305eb64e18b0273864920695cb18d7a2021f31a11b9c5fbcd9a253f936e2"}, "jason": {:hex, :jason, "1.2.0", "10043418c42d2493d0ee212d3fddd25d7ffe484380afad769a0a38795938e448", [:mix], [{:decimal, "~> 1.0", [hex: :decimal, repo: "hexpm", optional: true]}], "hexpm", "116747dbe057794c3a3e4e143b7c8390b29f634e16c78a7f59ba75bfa6852e7f"}, "makeup": {:hex, :makeup, "1.0.0", "671df94cf5a594b739ce03b0d0316aa64312cee2574b6a44becb83cd90fb05dc", [:mix], [{:nimble_parsec, "~> 0.5.0", [hex: :nimble_parsec, repo: "hexpm", optional: false]}], "hexpm", "a10c6eb62cca416019663129699769f0c2ccf39428b3bb3c0cb38c718a0c186d"}, diff --git a/test/ex_doc/autolink_test.exs b/test/ex_doc/autolink_test.exs index 2e96e772f..e470403e9 100644 --- a/test/ex_doc/autolink_test.exs +++ b/test/ex_doc/autolink_test.exs @@ -4,7 +4,7 @@ defmodule ExDoc.AutolinkTest do import ExUnit.CaptureIO defp sigil_m(text, []) do - [{:p, _, [ast]}] = ExDoc.Markdown.to_ast(text, []) + [{:p, _metadata, _attributes, [ast]}] = ExDoc.Markdown.to_ast(text, []) ast end @@ -220,7 +220,7 @@ defmodule ExDoc.AutolinkTest do assert_unchanged(" String.upcase()/2") assert_unchanged(":\"atom\"") assert_unchanged("1 + 2") - assert_unchanged({:p, [], ["hello"]}) + assert_unchanged({:p, %{}, [], ["hello"]}) end end @@ -386,8 +386,8 @@ defmodule ExDoc.AutolinkTest do assert autolink(ast_or_text, options) == ast(ast_or_text) end - defp ast(text) when is_binary(text), do: {:code, [class: "inline"], [text]} - defp ast({_, _, _} = ast), do: ast + defp ast(text) when is_binary(text), do: {:code, %{}, [class: "inline"], [text]} + defp ast({_, _, _, _} = ast), do: ast defp assert_warn(fun) do captured = capture_io(:stderr, fun) diff --git a/test/ex_doc/formatter/html/templates_test.exs b/test/ex_doc/formatter/html/templates_test.exs index 78ee4de47..479b22ad8 100644 --- a/test/ex_doc/formatter/html/templates_test.exs +++ b/test/ex_doc/formatter/html/templates_test.exs @@ -159,8 +159,7 @@ defmodule ExDoc.Formatter.HTML.TemplatesTest do defp to_html(markdown) do markdown |> ExDoc.Markdown.to_ast() - |> ExDoc.Formatter.HTML.ast_to_html() - |> IO.iodata_to_binary() + |> ExDoc.Markdown.AST.to_html() end describe "sidebar" do @@ -303,7 +302,6 @@ defmodule ExDoc.Formatter.HTML.TemplatesTest do describe "module_page" do test "outputs the functions and docstrings" do content = get_module_page([CompiledWithDocs]) - # Title and headers assert content =~ ~r{CompiledWithDocs [^<]*} @@ -407,6 +405,13 @@ defmodule ExDoc.Formatter.HTML.TemplatesTest do ~r{

.*.*.*.*Examples.*

}ms end + test "deals with special HTML characters" do + content = get_module_page([CompiledWithDocs]) + + assert content =~ + ~s{Another example with — & –} + end + ## BEHAVIOURS test "outputs behavior and callbacks" do diff --git a/test/ex_doc/formatter/html_test.exs b/test/ex_doc/formatter/html_test.exs index d1ca1c757..b7082a46b 100644 --- a/test/ex_doc/formatter/html_test.exs +++ b/test/ex_doc/formatter/html_test.exs @@ -398,6 +398,30 @@ defmodule ExDoc.Formatter.HTMLTest do assert content =~ ~r{"id":"extrapage","title":"Extra Page Title"} end + test "with HTML" do + generate_docs(doc_config(extras: ["test/fixtures/ExtraPageWithHTML.md"])) + content = File.read!("#{output_dir()}/extrapagewithhtml.html") + assert content =~ ~r{Extra Page with HTML — Elixir v1.0.1} + assert content =~ ~r{

\s*Extra Page with HTML\s*

} + assert content =~ ~r{

\s*Second Main Title\s*

} + assert content =~ ~r{

\s*\s*

} + + assert content =~ + ~r{

\s*

\s*
\s*\s*
\s*
\s*

} + + assert content =~ ~s{Elixir & Erlang} + + # Do not escape inside
+      assert content =~
+               ~r{
\s*
\s+inside pre & > <\s+Sample inside PRE\s*
} + + assert content =~ + ~r{
\s*\s*<samp>\s*Sample inside backticks\s*</samp>\s*\s*
} + + content = read_wildcard!("#{output_dir()}/dist/sidebar_items-*.js") + assert content =~ ~r{"id":"extrapagewithhtml","title":"Extra Page with HTML"} + end + test "without api-reference" do generate_docs( doc_config(api_reference: false, extras: ["test/fixtures/README.md"], main: "readme") diff --git a/test/ex_doc/markdown/earmark_test.exs b/test/ex_doc/markdown/earmark_test.exs index 4442feeb8..29264402a 100644 --- a/test/ex_doc/markdown/earmark_test.exs +++ b/test/ex_doc/markdown/earmark_test.exs @@ -7,9 +7,16 @@ defmodule ExDoc.Markdown.EarmarkTest do describe "to_ast/1" do test "generate AST" do - assert Markdown.to_ast("# Test\n\nHello", []) == [{:h1, [], ["Test"]}, {:p, [], ["Hello"]}] - assert Markdown.to_ast("[foo](bar)", []) == [{:p, [], [{:a, [href: "bar"], ["foo"]}]}] - assert Markdown.to_ast("

\nTest\n

", []) == [{:p, '', ["Test"]}] + assert Markdown.to_ast("# Test\n\nHello", []) == [ + {:h1, %{}, [], ["Test"]}, + {:p, %{}, [], ["Hello"]} + ] + + assert Markdown.to_ast("[foo](bar)", []) == [ + {:p, %{}, [], [{:a, %{}, [href: "bar"], ["foo"]}]} + ] + + assert Markdown.to_ast("

\nTest\n

", []) == [{:p, %{verbatim: true}, '', ["Test"]}] end test "empty input" do @@ -17,7 +24,9 @@ defmodule ExDoc.Markdown.EarmarkTest do end test "comments" do - assert Markdown.to_ast("", []) == [] + assert Markdown.to_ast("", []) == [ + {nil, %{comment: true}, [], [" INCLUDE "]} + ] end end end diff --git a/test/ex_doc/retriever_test.exs b/test/ex_doc/retriever_test.exs index 75aa3a3f2..3e25bec87 100644 --- a/test/ex_doc/retriever_test.exs +++ b/test/ex_doc/retriever_test.exs @@ -50,11 +50,11 @@ defmodule ExDoc.RetrieverTest do assert module_node.doc == [ - {:p, [], ["moduledoc"]}, - {:h2, [], ["Example ☃ Unicode > escaping"]}, - {:pre, [], [{:code, [], ["CompiledWithDocs.example"]}]}, - {:h3, [], ["Example H3 heading"]}, - {:p, [], ["example"]} + {:p, %{}, [], ["moduledoc"]}, + {:h2, %{}, [], ["Example ☃ Unicode > escaping"]}, + {:pre, %{}, [], [{:code, %{}, [], ["CompiledWithDocs.example"]}]}, + {:h3, %{}, [], ["Example H3 heading"]}, + {:p, %{}, [], ["example"]} ] end @@ -108,14 +108,14 @@ defmodule ExDoc.RetrieverTest do module_node.docs assert struct.id == "__struct__/0" - assert struct.doc == [{:p, [], ["Some struct"]}] + assert struct.doc == [{:p, %{}, [], ["Some struct"]}] assert struct.type == :function assert struct.defaults == [] assert struct.signature == "%CompiledWithDocs{}" assert struct.group == "Functions" assert example.id == "example/2" - assert example.doc == [{:p, [], ["Some example"]}] + assert example.doc == [{:p, %{}, [], ["Some example"]}] assert example.type == :function assert example.defaults == ["example/1"] assert example.signature == "example(foo, bar \\\\ Baz)" @@ -123,6 +123,11 @@ defmodule ExDoc.RetrieverTest do assert example.group == "Example" assert example_1.id == "example_1/0" + + assert example_1.doc == [ + {:p, %{}, [], ["Another example with — & – (— & –)"]} + ] + assert example_1.type == :macro assert example_1.defaults == [] assert example_1.annotations == ["macro", "since 1.3.0"] @@ -143,12 +148,17 @@ defmodule ExDoc.RetrieverTest do if Version.match?(System.version(), ">= 1.8.0") do assert flatten.doc == [ - {:p, [], ["See ", {:code, [], ["List.flatten/1"]}, "."]} + {:p, %{}, [], + [ + "See ", + {:code, %{}, [], ["List.flatten/1"]}, + "." + ]} ] end assert is_zero.id == "is_zero/1" - assert is_zero.doc == [{:p, [], ["A simple guard"]}] + assert is_zero.doc == [{:p, %{}, [], ["A simple guard"]}] assert is_zero.type == :macro assert is_zero.defaults == [] end @@ -188,7 +198,7 @@ defmodule ExDoc.RetrieverTest do assert public.arity == 1 assert public.id == "public/1" assert public.type == :type - assert public.doc == [{:p, [], ["A public type"]}] + assert public.doc == [{:p, %{}, [], ["A public type"]}] assert public.signature == "public(t)" assert Macro.to_string(public.spec) == @@ -283,23 +293,23 @@ defmodule ExDoc.RetrieverTest do assert Enum.map(docs, & &1.id) == ["bye/1", "greet/1", "hello/1"] assert Enum.at(docs, 0).doc == [ - {:p, [], + {:p, %{}, [], [ "Callback implementation for ", - {:code, [class: "inline"], ["c:CustomBehaviourTwo.bye/1"]}, + {:code, %{}, [class: "inline"], ["c:CustomBehaviourTwo.bye/1"]}, "." ]} ] assert Enum.at(docs, 1).doc == [ - {:p, [], ["A doc so it doesn't use 'Callback implementation for'"]} + {:p, %{}, [], ["A doc so it doesn't use 'Callback implementation for'"]} ] assert Enum.at(docs, 2).doc == [ - {:p, [], + {:p, %{}, [], [ "Callback implementation for ", - {:code, [class: "inline"], ["c:CustomBehaviourOne.hello/1"]}, + {:code, %{}, [class: "inline"], ["c:CustomBehaviourOne.hello/1"]}, "." ]} ] diff --git a/test/fixtures/ExtraPageWithHTML.md b/test/fixtures/ExtraPageWithHTML.md new file mode 100644 index 000000000..f91effd37 --- /dev/null +++ b/test/fixtures/ExtraPageWithHTML.md @@ -0,0 +1,62 @@ +

Extra Page with HTML

+ +

+ +

+ +

Hola

+ +Elixir & Erlang + +## Section One + +more text + +

Second Main Title

+ +more text + +### Code + +Inline code: `1 > 2`, `
` + +x + +```html +1 & 2 +1 > 2 +``` +y + + +```html + + +
+ +
foo
+``` + +```elixir +fn(x) -> x end +``` + + + + + +
+	
+ inside pre & > < + Sample inside PRE +
+ + +```html + + Sample inside backticks + +``` \ No newline at end of file diff --git a/test/fixtures/compiled_with_docs.ex b/test/fixtures/compiled_with_docs.ex index f48226ccd..6cba9864c 100644 --- a/test/fixtures/compiled_with_docs.ex +++ b/test/fixtures/compiled_with_docs.ex @@ -18,7 +18,7 @@ defmodule CompiledWithDocs do @deprecated "Use something else instead" def example(foo, bar \\ Baz), do: bar.baz(foo) - @doc "Another example" + @doc "Another example with — & – (— & –)" @doc since: "1.3.0" defmacro example_1, do: 1