Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
105 changes: 89 additions & 16 deletions lib/ex_doc/formatter/html/autolink.ex
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,60 @@ defmodule ExDoc.Formatter.HTML.Autolink do

@elixir_docs "https://hexdocs.pm/"
@erlang_docs "http://www.erlang.org/doc/man/"
@basic_types_page "typespecs.html#basic-types"
@built_in_types_page "typespecs.html#built-in-types"

@basic_types [
any: 0,
none: 0,
atom: 0,
map: 0,
pid: 0,
port: 0,
reference: 0,
struct: 0,
tuple: 0,
integer: 0,
float: 0,
neg_integer: 0,
non_neg_integer: 0,
pos_integer: 0,
list: 1,
nonempty_list: 1,
improper_list: 2,
maybe_improper_list: 2,
]

@built_in_types [
term: 0,
arity: 0,
as_boolean: 1,
binary: 0,
bitstring: 0,
boolean: 0,
byte: 0,
char: 0,
charlist: 0,
nonempty_charlist: 0,
fun: 0,
function: 0,
identifier: 0,
iodata: 0,
iolist: 0,
keyword: 0,
keyword: 1,
list: 0,
nonempty_list: 0,
maybe_improper_list: 0,
nonempty_maybe_improper_list: 0,
mfa: 0,
module: 0,
no_return: 0,
node: 0,
number: 0,
struct: 0,
timeout: 0
]

@doc """
Receives a list of module nodes and autolink all docs and typespecs.
Expand Down Expand Up @@ -153,6 +207,7 @@ defmodule ExDoc.Formatter.HTML.Autolink do

defp format_typespec(ast, typespecs, aliases, lib_dirs) do
ref = make_ref()
elixir_source = get_source(Kernel, aliases, lib_dirs)

{ast, placeholders} =
Macro.prewalk(ast, %{}, fn
Expand All @@ -166,26 +221,34 @@ defmodule ExDoc.Formatter.HTML.Autolink do
{name, _, args} = form, placeholders when is_atom(name) and is_list(args) ->
arity = length(args)

if {name, arity} in typespecs do
string = Macro.to_string(form)
n = enc_h("#{name}")
{string_to_link, _string_with_parens} = split_string_to_link(string)
string = ~s[<a href="#t:#{n}/#{arity}">#{h(string_to_link)}</a>]

put_placeholder(form, string, placeholders)
else
{form, placeholders}
cond do
{name, arity} in @basic_types ->
url = elixir_source <> @basic_types_page
string = format_typespec_form(form, url)
put_placeholder(form, string, placeholders)

{name, arity} in @built_in_types ->
url = elixir_source <> @built_in_types_page
string = format_typespec_form(form, url)
put_placeholder(form, string, placeholders)

{name, arity} in typespecs ->
n = enc_h("#{name}")
url = "#t:#{n}/#{arity}"
string = format_typespec_form(form, url)
put_placeholder(form, string, placeholders)

true ->
{form, placeholders}
end

{{:., _, [alias, name]}, _, args} = form, placeholders when is_atom(name) and is_list(args) ->
alias = expand_alias(alias)

if source = get_source(alias, aliases, lib_dirs) do
string = Macro.to_string(form)
n = enc_h("#{name}")
{string_to_link, _string_with_parens} = split_string_to_link(string)
string = ~s[<a href="#{source}#{enc_h(inspect alias)}.html#t:#{n}/#{length(args)}">#{h(string_to_link)}</a>]

url = "#{source}#{enc_h(inspect alias)}.html#t:#{n}/#{length(args)}"
string = format_typespec_form(form, url)
put_placeholder(form, string, placeholders)
else
{form, placeholders}
Expand All @@ -200,15 +263,25 @@ defmodule ExDoc.Formatter.HTML.Autolink do
|> replace_placeholders(placeholders)
end

defp format_typespec_form(form, url) do
string = Macro.to_string(form)
{string_to_link, _string_with_parens} = split_string_to_link(string)
~s[<a href="#{url}">#{h(string_to_link)}</a>]
end

defp put_placeholder(form, string, placeholders) do
id = map_size(placeholders)
placeholder = :"_p#{id}_"
count = map_size(placeholders) + 1
type_size = form |> Macro.to_string() |> byte_size()
int_size = count |> Integer.to_string() |> byte_size()
parens_size = 2
pad = String.duplicate("p", max(type_size - int_size - parens_size, 1))
placeholder = :"#{pad}#{count}"
form = put_elem(form, 0, placeholder)
{form, Map.put(placeholders, Atom.to_string(placeholder), string)}
end

defp replace_placeholders(string, placeholders) do
Regex.replace(~r"_p\d+_", string, &Map.fetch!(placeholders, &1))
Regex.replace(~r"p+\d+", string, &Map.fetch!(placeholders, &1))
end

defp format_ast(ast) do
Expand Down
41 changes: 32 additions & 9 deletions test/ex_doc/formatter/html/autolink_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -181,11 +181,11 @@ defmodule ExDoc.Formatter.HTML.AutolinkTest do
# typespec

test "operators" do
assert Autolink.typespec(quote(do: +number() :: number()), [], [], []) ==
~s[+number() :: number()]
assert Autolink.typespec(quote(do: +foo() :: foo()), [], [], []) ==
~s[+foo() :: foo()]

assert Autolink.typespec(quote(do: number() + number() :: number()), [], [], []) ==
~s[number() + number() :: number()]
assert Autolink.typespec(quote(do: foo() + foo() :: foo()), [], [], []) ==
~s[foo() + foo() :: foo()]
end

test "strip parens in typespecs" do
Expand Down Expand Up @@ -256,14 +256,14 @@ defmodule ExDoc.Formatter.HTML.AutolinkTest do
test "complex types with formatter" do
ast = quote do
t() :: %{
foo: term(),
foo: bar(),
really_long_name_that_will_trigger_multiple_line_breaks: String.t()
}
end

assert Autolink.typespec(ast, [], []) == String.trim("""
t() :: %{
foo: term(),
foo: bar(),
really_long_name_that_will_trigger_multiple_line_breaks: <a href=\"https://hexdocs.pm/elixir/String.html#t:t/0\">String.t</a>()
}
""")
Expand All @@ -273,13 +273,13 @@ defmodule ExDoc.Formatter.HTML.AutolinkTest do
test "complex types without formatter" do
ast = quote do
t() :: %{
foo: term(),
foo: bar(),
really_long_name_that_will_trigger_multiple_line_breaks: String.t()
}
end

assert Autolink.typespec(ast, [], []) ==
~s[t() :: %{foo: term(), really_long_name_that_will_trigger_multiple_line_breaks: <a href=\"https://hexdocs.pm/elixir/String.html#t:t/0\">String.t</a>()}]
~s[t() :: %{foo: bar(), really_long_name_that_will_trigger_multiple_line_breaks: <a href=\"https://hexdocs.pm/elixir/String.html#t:t/0\">String.t</a>()}]
end

test "autolink Elixir types in typespecs" do
Expand All @@ -290,12 +290,27 @@ defmodule ExDoc.Formatter.HTML.AutolinkTest do
~s[Unknown.bar()]
end

test "autolink Elixir basic types in typespecs" do
assert Autolink.typespec(quote(do: atom()), [], []) ==
~s[<a href=\"https://hexdocs.pm/elixir/typespecs.html#basic-types\">atom</a>()]
end

test "autolink Elixir built-in types in typespecs" do
assert Autolink.typespec(quote(do: term()), [], []) ==
~s[<a href=\"https://hexdocs.pm/elixir/typespecs.html#built-in-types\">term</a>()]
end

test "autolink Elixir built-in types in Elixir typespecs" do
assert Autolink.typespec(quote(do: term()), [], [Kernel]) ==
~s[<a href=\"typespecs.html#built-in-types\">term</a>()]
end

test "autolink shared aliases in typespecs" do
assert Autolink.typespec(quote(do: Foo.t), [], [Foo]) ==
~s[<a href="Foo.html#t:t/0">Foo.t</a>()]
end

test "autolink local and remote types inside parameterized types" do
test "autolink local remote basic built-in types inside parameterized types" do
assert Autolink.typespec(quote(do: parameterized_t(foo())), [parameterized_t: 1, foo: 0], []) ==
~s[<a href="#t:parameterized_t/1">parameterized_t</a>(<a href="#t:foo/0">foo</a>())]

Expand All @@ -316,5 +331,13 @@ defmodule ExDoc.Formatter.HTML.AutolinkTest do

assert Autolink.typespec(quote(do: parameterized_t(foo())), [foo: 0], []) ==
~s[parameterized_t(<a href="#t:foo/0">foo</a>())]

assert Autolink.typespec(quote(do: parameterized_t(atom())), [], []) ==
~s[parameterized_t(<a href=\"https://hexdocs.pm/elixir/typespecs.html#basic-types\">atom</a>())]

assert Autolink.typespec(quote(do: parameterized_t(atom()) :: list(function())), [], []) ==
~s[parameterized_t(<a href=\"https://hexdocs.pm/elixir/typespecs.html#basic-types\">atom</a>()) :: ] <>
~s[<a href=\"https://hexdocs.pm/elixir/typespecs.html#basic-types\">list</a>(] <>
~s[<a href=\"https://hexdocs.pm/elixir/typespecs.html#built-in-types\">function</a>())]
end
end
8 changes: 5 additions & 3 deletions test/ex_doc/formatter/html/templates_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -252,23 +252,25 @@ defmodule ExDoc.Formatter.HTML.TemplatesTest do

test "module_page outputs the types and function specs" do
content = get_module_page([TypesAndSpecs, TypesAndSpecs.Sub])
any = ~s[<a href="https://hexdocs.pm/elixir/typespecs.html#basic-types">any</a>()]
integer = ~s[<a href="https://hexdocs.pm/elixir/typespecs.html#basic-types">integer</a>()]

public_html =
~S[public(t) :: {t, ] <>
~s[<a href="https://hexdocs.pm/elixir/String.html#t:t/0">String.t</a>(), ] <>
~S[<a href="TypesAndSpecs.Sub.html#t:t/0">TypesAndSpecs.Sub.t</a>(), ] <>
~S[<a href="#t:opaque/0">opaque</a>(), :ok | :error}]

ref_html = ~S[ref() :: {:binary.part(), <a href="#t:public/1">public</a>(any())}]
ref_html = ~s[ref() :: {:binary.part(), <a href="#t:public/1">public</a>(#{any})}]

assert content =~ ~s[<a href="#t:public/1">public(t)</a>]
refute content =~ ~s[<a href="#t:private/0">private</a>]
assert content =~ public_html
assert content =~ ref_html
refute content =~ ~s[<strong>private\(t\)]
assert content =~ ~s[A public type]
assert content =~ ~s[add(integer(), <a href="#t:opaque/0">opaque</a>()) :: integer()]
refute content =~ ~s[minus(integer(), integer()) :: integer()]
assert content =~ ~s[add(#{integer}, <a href="#t:opaque/0">opaque</a>()) :: #{integer}]
refute content =~ ~s[minus(#{integer}, #{integer}) :: #{integer}]
end

test "module_page outputs summaries" do
Expand Down