From 1fdd3fa0dadcb2574486ef6173bdd8d77c5ec794 Mon Sep 17 00:00:00 2001
From: ruslandoga <67764432+ruslandoga@users.noreply.github.com>
Date: Thu, 30 May 2024 16:53:48 +0700
Subject: [PATCH 1/5] replace OTP /man/ links with /apps/:app/
---
lib/ex_doc/autolink.ex | 31 ++++++++++----
test/ex_doc/formatter/html/erlang_test.exs | 4 +-
test/ex_doc/language/elixir_test.exs | 16 +++----
test/ex_doc/language/erlang_test.exs | 50 +++++++++++-----------
test/ex_doc/retriever/erlang_test.exs | 6 +--
5 files changed, 61 insertions(+), 46 deletions(-)
diff --git a/lib/ex_doc/autolink.ex b/lib/ex_doc/autolink.ex
index f5af58bd2..1260e13e8 100644
--- a/lib/ex_doc/autolink.ex
+++ b/lib/ex_doc/autolink.ex
@@ -63,7 +63,6 @@ defmodule ExDoc.Autolink do
]
@hexdocs "https://hexdocs.pm/"
- @otpdocs "https://www.erlang.org/doc/man/"
@otpappdocs "https://www.erlang.org/doc/apps/"
def app_module_url(tool, module, anchor \\ nil, config)
@@ -72,18 +71,30 @@ defmodule ExDoc.Autolink do
app_module_url(:ex_doc, module, "#content", config)
end
- def app_module_url(:ex_doc, module, anchor, %{current_module: module} = config) do
+ def app_module_url(:ex_doc, module, anchor, config) do
path = module |> inspect() |> String.trim_leading(":")
ex_doc_app_url(module, config, path, config.ext, "#{anchor}")
end
- def app_module_url(:ex_doc, module, anchor, config) do
- path = module |> inspect() |> String.trim_leading(":")
- ex_doc_app_url(module, config, path, config.ext, "#{anchor}")
+ def app_module_url(:otp, module, nil, %{current_module: module} = config) do
+ app_module_url(:otp, module, "#content", config)
end
- def app_module_url(:otp, module, anchor, _config) do
- @otpdocs <> "#{module}.html#{anchor}"
+ def app_module_url(:otp, module, anchor, config) do
+ path = module |> inspect() |> String.trim_leading(":")
+
+ # IO.inspect(
+ # [
+ # module: module,
+ # anchor: anchor,
+ # config: config,
+ # prev: @otpdocs <> "#{module}.html#{anchor}",
+ # new: app_url(@otpappdocs, module, config, path, config.ext, "#{anchor}")
+ # ],
+ # label: "app_module_url"
+ # )
+
+ app_url(@otpappdocs, module, config, path, config.ext, "#{anchor}")
end
def app_module_url(:no_tool, _, _, _) do
@@ -109,12 +120,16 @@ defmodule ExDoc.Autolink do
@doc false
def ex_doc_app_url(module, config, path, ext, suffix) do
+ app_url(@hexdocs, module, config, path, ext, suffix)
+ end
+
+ defp app_url(base_url, module, config, path, ext, suffix) do
if app = app(module) do
if app in config.apps do
path <> ext <> suffix
else
config.deps
- |> Keyword.get_lazy(app, fn -> @hexdocs <> "#{app}" end)
+ |> Keyword.get_lazy(app, fn -> base_url <> "#{app}" end)
|> String.trim_trailing("/")
|> Kernel.<>("/" <> path <> ".html" <> suffix)
end
diff --git a/test/ex_doc/formatter/html/erlang_test.exs b/test/ex_doc/formatter/html/erlang_test.exs
index 5ef9d6aaf..67db25ca3 100644
--- a/test/ex_doc/formatter/html/erlang_test.exs
+++ b/test/ex_doc/formatter/html/erlang_test.exs
@@ -36,10 +36,10 @@ defmodule ExDoc.Formatter.HTML.ErlangTest do
~s|-spec foo(t()) -> t().|
assert html =~
- ~s|-type t() :: atom().|
+ ~s|-type t() :: atom().|
assert html =~
- ~s|-type t2() :: #rec{k1 :: uri_string:uri_string(), k2 :: uri_string:uri_string() \| undefined}.|
+ ~s|-type t2() :: #rec{k1 :: uri_string:uri_string(), k2 :: uri_string:uri_string() \| undefined}.|
end
defp generate_docs(c) do
diff --git a/test/ex_doc/language/elixir_test.exs b/test/ex_doc/language/elixir_test.exs
index 7685d871c..69b4b8eb4 100644
--- a/test/ex_doc/language/elixir_test.exs
+++ b/test/ex_doc/language/elixir_test.exs
@@ -40,12 +40,12 @@ defmodule ExDoc.Language.ElixirTest do
test "m:module with Erlang module" do
assert autolink_doc("`m::array`") ==
- ~s|:array
|
+ ~s|:array
|
end
test "m:module with Erlang module and fragment" do
assert autolink_doc("`m::array#fragment`") ==
- ~s|:array
|
+ ~s|:array
|
end
test "module with fragment without m: does not link" do
@@ -99,7 +99,7 @@ defmodule ExDoc.Language.ElixirTest do
test "erlang stdlib function" do
assert autolink_doc("`:lists.all/2`") ==
- ~s|:lists.all/2
|
+ ~s|:lists.all/2
|
end
test "local function" do
@@ -150,7 +150,7 @@ defmodule ExDoc.Language.ElixirTest do
test "erlang callback" do
assert autolink_doc("`c::gen_server.handle_call/3`") ==
- ~s|:gen_server.handle_call/3
|
+ ~s|:gen_server.handle_call/3
|
end
test "elixir type" do
@@ -171,7 +171,7 @@ defmodule ExDoc.Language.ElixirTest do
test "erlang type" do
assert autolink_doc("`t::array.array/0`") ==
- ~s|:array.array/0
|
+ ~s|:array.array/0
|
end
test "special forms" do
@@ -204,10 +204,10 @@ defmodule ExDoc.Language.ElixirTest do
~s|custom text|
assert autolink_doc("[custom text](`:lists`)") ==
- ~s|custom text|
+ ~s|custom text|
assert autolink_doc("[custom text](`:lists.all/2`)") ==
- ~s|custom text|
+ ~s|custom text|
end
test "mix task" do
@@ -450,7 +450,7 @@ defmodule ExDoc.Language.ElixirTest do
test "Erlang stdlib types" do
assert autolink_spec(quote(do: t() :: :sets.set())) ==
- ~s[t() :: :sets.set()]
+ ~s[t() :: :sets.set()]
end
test "escape special HTML characters" do
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index 888bdf1f8..f15bb66a2 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -20,7 +20,7 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP module", c do
assert autolink_edoc("{@link array}", c) ==
- ~s|array
|
+ ~s|array
|
end
test "OTP module when generating OTP docs", c do
@@ -30,7 +30,7 @@ defmodule ExDoc.Language.ErlangTest do
test "app module", c do
assert autolink_edoc("{@link //stdlib/array}", c) ==
- ~s|array
|
+ ~s|array
|
end
@tag warnings: :send
@@ -57,19 +57,19 @@ defmodule ExDoc.Language.ErlangTest do
[{:code, [], ["array"], %{}}], %{}}
assert do_autolink_doc(ast) ==
- ~s|array
|
+ ~s|array
|
ast =
{:a, [href: "stdlib:array#anchor", rel: "https://erlang.org/doc/link/seeerl"],
[{:code, [], ["array"], %{}}], %{}}
assert do_autolink_doc(ast) ==
- ~s|array
|
+ ~s|array
|
end
test "custom text", c do
assert autolink_edoc("{@link array. The array
module}", c) ==
- ~s|The array
module|
+ ~s|The array
module|
end
test "local function", c do
@@ -84,7 +84,7 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP function", c do
assert autolink_edoc("{@link array:new/0}", c) ==
- ~s|array:new/0
|
+ ~s|array:new/0
|
end
test "OTP function when generating OTP docs", c do
@@ -99,12 +99,12 @@ defmodule ExDoc.Language.ErlangTest do
test "ERTS function", c do
assert autolink_edoc("{@link zlib:gunzip/1}", c) ==
- ~s|zlib:gunzip/1
|
+ ~s|zlib:gunzip/1
|
end
test "app function", c do
assert autolink_edoc("{@link //stdlib/array:new/0}", c) ==
- ~s|array:new/0
|
+ ~s|array:new/0
|
end
test "external function", c do
@@ -124,12 +124,12 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP type", c do
assert autolink_edoc("{@link array:array()}", c) ==
- ~s|array:array()
|
+ ~s|array:array()
|
end
test "app type", c do
assert autolink_edoc("{@link //stdlib/array:array()}", c) ==
- ~s|array:array()
|
+ ~s|array:array()
|
end
@myList (if :erlang.system_info(:otp_release) >= ~c"27" do
@@ -310,7 +310,7 @@ defmodule ExDoc.Language.ErlangTest do
test "function in module autoimport using slash", c do
assert autolink_doc("`node/0`", c) ==
- ~s|node/0
|
+ ~s|node/0
|
end
test "type in module autoimport", c do
@@ -320,7 +320,7 @@ defmodule ExDoc.Language.ErlangTest do
test "type in module autoimport using slash", c do
assert autolink_doc("`t:integer/0`", c) ==
- ~s|integer/0
|
+ ~s|integer/0
|
end
test "bad function in module code", c do
@@ -335,7 +335,7 @@ defmodule ExDoc.Language.ErlangTest do
test "linking to auto-imported nil works", c do
assert autolink_doc("[`[]`](`t:nil/0`)", c) ==
- ~s|[]
|
+ ~s|[]
|
end
test "linking to local nil works", c do
@@ -543,7 +543,7 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP function", c do
assert autolink_extra("`lists:reverse/1`", c) ==
- ~s|lists:reverse/1
|
+ ~s|lists:reverse/1
|
end
test "type", c do
@@ -553,7 +553,7 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP type", c do
assert autolink_extra("`t:array:array/0`", c) ==
- ~s|array:array/0
|
+ ~s|array:array/0
|
end
test "module", c do
@@ -563,7 +563,7 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP module", c do
assert autolink_extra("`m:rpc`", c) ==
- ~s|rpc
|
+ ~s|rpc
|
end
test "bad module function", c do
@@ -684,9 +684,9 @@ defmodule ExDoc.Language.ErlangTest do
test "spec when fun is called record", c do
assert autolink_spec("-spec record(module()) -> [[{module(), atom()}]].", c) ==
- ~s|record(module())| <>
- ~s| -> [[{module(),| <>
- ~s| atom()}]].|
+ ~s|record(module())| <>
+ ~s| -> [[{module(),| <>
+ ~s| atom()}]].|
end
test "callback", c do
@@ -724,7 +724,7 @@ defmodule ExDoc.Language.ErlangTest do
~S"-spec foo() -> #{atom() := sets:set(integer()), float() => t()}.",
c
) ==
- ~S|foo() -> #{atom() := sets:set(integer()), float() => t()}.|
+ ~S|foo() -> #{atom() := sets:set(integer()), float() => t()}.|
end
test "vars", c do
@@ -744,12 +744,12 @@ defmodule ExDoc.Language.ErlangTest do
test "record - one field", c do
assert autolink_spec(~s"-spec foo() -> #x{x :: atom()} | t().", c) ==
- ~s[foo() -> #x{x :: atom()} | t().]
+ ~s[foo() -> #x{x :: atom()} | t().]
end
test "record - two fields", c do
assert autolink_spec(~s"-spec foo() -> #x{x :: atom(), y :: sets:set(integer())} | t().", c) ==
- ~s[foo() -> #x{x :: atom(), y :: sets:set(integer())} | t().]
+ ~s[foo() -> #x{x :: atom(), y :: sets:set(integer())} | t().]
end
test "record - two fields, known types", c do
@@ -789,12 +789,12 @@ defmodule ExDoc.Language.ErlangTest do
test "OTP type", c do
assert autolink_spec(~S"-spec foo() -> sets:set().", c) ==
- ~s|foo() -> sets:set().|
+ ~s|foo() -> sets:set().|
end
test "OTP private type", c do
assert autolink_spec(~S"-spec foo() -> array:array_indx().", c) ==
- ~s|foo() -> array:array_indx().|
+ ~s|foo() -> array:array_indx().|
end
test "skip typespec name", c do
@@ -820,7 +820,7 @@ defmodule ExDoc.Language.ErlangTest do
test "bad remote type", c do
assert warn(fn ->
assert autolink_spec(~S"-spec foo() -> bad:bad(atom()).", c, warnings: :send) ==
- ~s|foo() -> bad:bad(atom()).|
+ ~s|foo() -> bad:bad(atom()).|
end) =~ ~s|references type "bad:bad/1" but it is undefined or private|
end
end
diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs
index 6075d60ae..fd0ba74c0 100644
--- a/test/ex_doc/retriever/erlang_test.exs
+++ b/test/ex_doc/retriever/erlang_test.exs
@@ -415,7 +415,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert DocAST.to_string(function1.doc) =~ "function1/0 docs."
assert Erlang.autolink_spec(hd(function1.specs), current_kfa: {:function, :function1, 0}) ==
- "function1() -> atom()."
+ "function1() -> atom()."
%ExDoc.FunctionNode{
id: "function2/0"
@@ -463,7 +463,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert Path.basename(callback1.source_url) == "mod.erl:4"
assert Erlang.autolink_spec(hd(callback1.specs), current_kfa: {:callback, :callback1, 0}) ==
- "callback1() -> atom()."
+ "callback1() -> atom()."
assert optional_callback1.id == "c:optional_callback1/0"
assert optional_callback1.type == :callback
@@ -501,7 +501,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert type1.doc |> DocAST.to_string() =~ "type1/0 docs."
assert type1.spec |> Erlang.autolink_spec(current_kfa: {:type, :type1, 0}) ==
- "type1() :: atom()."
+ "type1() :: atom()."
end
end
end
From 3be1dc9bb3dbd13e0d10ffae072df4c005508ddb Mon Sep 17 00:00:00 2001
From: ruslandoga <67764432+ruslandoga@users.noreply.github.com>
Date: Thu, 30 May 2024 17:00:29 +0700
Subject: [PATCH 2/5] cleanup
---
lib/ex_doc/autolink.ex | 39 +++++++---------------------
test/ex_doc/language/erlang_test.exs | 2 +-
2 files changed, 10 insertions(+), 31 deletions(-)
diff --git a/lib/ex_doc/autolink.ex b/lib/ex_doc/autolink.ex
index 1260e13e8..b26d55df5 100644
--- a/lib/ex_doc/autolink.ex
+++ b/lib/ex_doc/autolink.ex
@@ -65,40 +65,19 @@ defmodule ExDoc.Autolink do
@hexdocs "https://hexdocs.pm/"
@otpappdocs "https://www.erlang.org/doc/apps/"
- def app_module_url(tool, module, anchor \\ nil, config)
+ def app_module_url(tool, module, anchor \\ "#content", config)
- def app_module_url(:ex_doc, module, nil, %{current_module: module} = config) do
- app_module_url(:ex_doc, module, "#content", config)
- end
+ def app_module_url(:no_tool, _, _, _), do: nil
- def app_module_url(:ex_doc, module, anchor, config) do
- path = module |> inspect() |> String.trim_leading(":")
- ex_doc_app_url(module, config, path, config.ext, "#{anchor}")
- end
-
- def app_module_url(:otp, module, nil, %{current_module: module} = config) do
- app_module_url(:otp, module, "#content", config)
- end
+ def app_module_url(tool, module, anchor, config) do
+ base_url =
+ case tool do
+ :ex_doc -> @hexdocs
+ :otp -> @otpappdocs
+ end
- def app_module_url(:otp, module, anchor, config) do
path = module |> inspect() |> String.trim_leading(":")
-
- # IO.inspect(
- # [
- # module: module,
- # anchor: anchor,
- # config: config,
- # prev: @otpdocs <> "#{module}.html#{anchor}",
- # new: app_url(@otpappdocs, module, config, path, config.ext, "#{anchor}")
- # ],
- # label: "app_module_url"
- # )
-
- app_url(@otpappdocs, module, config, path, config.ext, "#{anchor}")
- end
-
- def app_module_url(:no_tool, _, _, _) do
- nil
+ app_url(base_url, module, config, path, config.ext, "#{anchor}")
end
defp string_app_module_url(string, tool, module, anchor, config) do
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index f15bb66a2..835ea8a08 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -15,7 +15,7 @@ defmodule ExDoc.Language.ErlangTest do
test "current module", c do
assert autolink_edoc("{@link erlang_foo}", c, current_module: :erlang_foo) ==
- ~s|erlang_foo
|
+ ~s|erlang_foo
|
end
test "OTP module", c do
From e46818022730d510c6f6b9a04c8f170f59cd9acd Mon Sep 17 00:00:00 2001
From: ruslandoga <67764432+ruslandoga@users.noreply.github.com>
Date: Thu, 30 May 2024 17:15:01 +0700
Subject: [PATCH 3/5] update tests tagged with :otp_eep59
---
test/ex_doc/formatter/html/erlang_test.exs | 6 ++---
test/ex_doc/language/erlang_test.exs | 26 +++++++++++-----------
test/ex_doc/retriever/erlang_test.exs | 10 ++++-----
3 files changed, 21 insertions(+), 21 deletions(-)
diff --git a/test/ex_doc/formatter/html/erlang_test.exs b/test/ex_doc/formatter/html/erlang_test.exs
index 67db25ca3..4c7edc9cf 100644
--- a/test/ex_doc/formatter/html/erlang_test.exs
+++ b/test/ex_doc/formatter/html/erlang_test.exs
@@ -33,13 +33,13 @@ defmodule ExDoc.Formatter.HTML.ErlangTest do
html = Floki.raw_html(doc)
assert html =~
- ~s|-spec foo(t()) -> t().|
+ ~s|-spec foo(t()) -> t().|
assert html =~
- ~s|-type t() :: atom().|
+ ~s|-type t() :: atom().|
assert html =~
- ~s|-type t2() :: #rec{k1 :: uri_string:uri_string(), k2 :: uri_string:uri_string() \| undefined}.|
+ ~s|-type t2() :: #rec{k1 :: uri_string:uri_string(), k2 :: uri_string:uri_string() \| undefined}.|
end
defp generate_docs(c) do
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index 835ea8a08..6b16eb4d0 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -142,21 +142,21 @@ defmodule ExDoc.Language.ErlangTest do
assert autolink_edoc("{@type myList(X). A special kind of lists ...}", c,
extra_foo_code: "-export_type([myList/0]).\n-type myList() :: term().\n%% A type"
) ==
- ~s|myList(X)
|
+ ~s|myList(X)
|
end
test "abstract types - description+dot", c do
assert autolink_edoc("{@type myList(X, Y).}", c,
extra_foo_code: "-export_type([myList/0]).\n-type myList() :: term().\n%% A type"
) ==
- ~s|myList(X, Y)
|
+ ~s|myList(X, Y)
|
end
test "abstract types - no description", c do
assert autolink_edoc("{@type myList()}", c,
extra_foo_code: "-export_type([myList/0]).\n-type myList() :: term().\n%% A type"
) ==
- ~s|myList()
|
+ ~s|myList()
|
end
end
@@ -226,12 +226,12 @@ defmodule ExDoc.Language.ErlangTest do
test "m:module in module code", c do
assert autolink_doc("`m:erlang_bar`", c) ==
- ~s|erlang_bar
|
+ ~s|erlang_bar
|
end
test "m:module with anchor in module code", c do
assert autolink_doc("`m:erlang_bar#anchor`", c) ==
- ~s|erlang_bar
|
+ ~s|erlang_bar
|
end
test "invalid m:module in module code", c do
@@ -241,28 +241,28 @@ defmodule ExDoc.Language.ErlangTest do
test "module in module code reference", c do
assert autolink_doc("[`erlang_bar`](`erlang_bar`)", c) ==
- ~s|erlang_bar
|
+ ~s|erlang_bar
|
end
test "remote module with anchor in module code reference", c do
assert autolink_doc("[`erlang_bar`](`erlang_bar#anchor`)", c) ==
- ~s|erlang_bar
|
+ ~s|erlang_bar
|
assert autolink_doc("[`erlang_bar`](`m:erlang_bar#anchor`)", c) ==
- ~s|erlang_bar
|
+ ~s|erlang_bar
|
end
test "own module with anchor in module code reference", c do
assert autolink_doc("[`erlang_foo`](`erlang_foo#anchor`)", c) ==
- ~s|erlang_foo
|
+ ~s|erlang_foo
|
assert autolink_doc("[`erlang_foo`](`m:erlang_foo#anchor`)", c) ==
- ~s|erlang_foo
|
+ ~s|erlang_foo
|
end
test "function in module code", c do
assert autolink_doc("`foo/0`", c) ==
- ~s|foo/0
|
+ ~s|foo/0
|
end
test "function in module ref", c do
@@ -498,7 +498,7 @@ defmodule ExDoc.Language.ErlangTest do
assert warn(
fn ->
assert autolink_doc("[extra](`e:barlib:extra.md`)", c) ==
- ~s|extra|
+ ~s|extra|
end,
line: nil
) =~
@@ -509,7 +509,7 @@ defmodule ExDoc.Language.ErlangTest do
assert warn(
fn ->
assert autolink_doc("[extra](`e:barlib:extra.md#anchor`)", c) ==
- ~s|extra|
+ ~s|extra|
end,
line: nil
) =~
diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs
index fd0ba74c0..341b88515 100644
--- a/test/ex_doc/retriever/erlang_test.exs
+++ b/test/ex_doc/retriever/erlang_test.exs
@@ -93,7 +93,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert function1.doc_file =~ "mod.erl"
assert Erlang.autolink_spec(hd(function1.specs), current_kfa: {:function, :function1, 0}) ==
- "function1() -> atom()."
+ "function1() -> atom()."
%ExDoc.FunctionNode{
id: "function2/1"
@@ -293,7 +293,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert opaque1.id == "t:opaque1/0"
assert opaque1.type == :opaque
assert opaque1.group == :Types
- assert opaque1.signature == "opaque1()"
+ assert opaque1.signature == "opaque1/0"
assert opaque1.doc |> DocAST.to_string() =~ "opaque1/0 docs."
assert opaque1.spec |> Erlang.autolink_spec(current_kfa: {:type, :opaque1, 0}) ==
@@ -341,15 +341,15 @@ defmodule ExDoc.Retriever.ErlangTest do
assert hd(function.specs)
|> Erlang.autolink_spec(current_module: :mod, current_kfa: {:function, :function, 0}) ==
- "function() -> type() | #a{a :: integer(), b :: integer(), c :: atom(), d :: term(), e :: term()}."
+ "function() -> type() | #a{a :: integer(), b :: integer(), c :: atom(), d :: term(), e :: term()}."
assert hd(callback.specs)
|> Erlang.autolink_spec(current_module: :mod, current_kfa: {:callback, :callback, 0}) ==
- "callback() ->\n #a{a :: pos_integer(), b :: non_neg_integer(), c :: atom(), d :: term(), e :: term()}."
+ "callback() ->\n #a{a :: pos_integer(), b :: non_neg_integer(), c :: atom(), d :: term(), e :: term()}."
assert type.spec
|> Erlang.autolink_spec(current_module: :mod, current_kfa: {:type, :type, 0}) ==
- "type() :: #a{a :: pos_integer(), b :: non_neg_integer(), c :: atom(), d :: term(), e :: term()}."
+ "type() :: #a{a :: pos_integer(), b :: non_neg_integer(), c :: atom(), d :: term(), e :: term()}."
end
end
From caa27789d706305c4bdfb4a80a5dc659f0629e68 Mon Sep 17 00:00:00 2001
From: ruslandoga <67764432+ruslandoga@users.noreply.github.com>
Date: Thu, 30 May 2024 17:59:33 +0700
Subject: [PATCH 4/5] update eerp59 tests
---
test/ex_doc/language/erlang_test.exs | 2 +-
test/ex_doc/retriever/erlang_test.exs | 4 ++--
2 files changed, 3 insertions(+), 3 deletions(-)
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index 6b16eb4d0..fe94b883f 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -774,7 +774,7 @@ defmodule ExDoc.Language.ErlangTest do
test "function - any arity", c do
assert autolink_spec(~s"-spec foo() -> fun((...) -> t()) | erlang_bar:t().", c) ==
- ~s[foo() -> fun((...) -> t()) | erlang_bar:t().]
+ ~s[foo() -> fun((...) -> t()) | erlang_bar:t().]
end
test "local type", c do
diff --git a/test/ex_doc/retriever/erlang_test.exs b/test/ex_doc/retriever/erlang_test.exs
index 341b88515..a97dc08de 100644
--- a/test/ex_doc/retriever/erlang_test.exs
+++ b/test/ex_doc/retriever/erlang_test.exs
@@ -253,7 +253,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert Path.basename(callback1.source_url) == "mod.erl:4"
assert Erlang.autolink_spec(hd(callback1.specs), current_kfa: {:callback, :callback1, 0}) ==
- "callback1() -> atom()."
+ "callback1() -> atom()."
assert equiv_callback1.id == "c:equiv_callback1/0"
assert equiv_callback1.type == :callback
@@ -293,7 +293,7 @@ defmodule ExDoc.Retriever.ErlangTest do
assert opaque1.id == "t:opaque1/0"
assert opaque1.type == :opaque
assert opaque1.group == :Types
- assert opaque1.signature == "opaque1/0"
+ assert opaque1.signature == "opaque1()"
assert opaque1.doc |> DocAST.to_string() =~ "opaque1/0 docs."
assert opaque1.spec |> Erlang.autolink_spec(current_kfa: {:type, :opaque1, 0}) ==
From 77598cdb50236591e86ac7fbb6024c0e345c4a79 Mon Sep 17 00:00:00 2001
From: ruslandoga <67764432+ruslandoga@users.noreply.github.com>
Date: Thu, 30 May 2024 18:02:49 +0700
Subject: [PATCH 5/5] fix ci
---
test/ex_doc/language/erlang_test.exs | 2 +-
1 file changed, 1 insertion(+), 1 deletion(-)
diff --git a/test/ex_doc/language/erlang_test.exs b/test/ex_doc/language/erlang_test.exs
index fe94b883f..6b16eb4d0 100644
--- a/test/ex_doc/language/erlang_test.exs
+++ b/test/ex_doc/language/erlang_test.exs
@@ -774,7 +774,7 @@ defmodule ExDoc.Language.ErlangTest do
test "function - any arity", c do
assert autolink_spec(~s"-spec foo() -> fun((...) -> t()) | erlang_bar:t().", c) ==
- ~s[foo() -> fun((...) -> t()) | erlang_bar:t().]
+ ~s[foo() -> fun((...) -> t()) | erlang_bar:t().]
end
test "local type", c do