File 2751-kernel-Fix-code-get_doc-1-2-when-cover_compiled.patch of Package erlang
From 06adfb27cdc212368bbf0de1bba97cfa4c6384d5 Mon Sep 17 00:00:00 2001
From: williamthome <williamthome@hotmail.com>
Date: Thu, 13 Feb 2025 09:53:41 -0300
Subject: [PATCH] kernel: Fix `code:get_doc/1,2` when cover_compiled
---
lib/compiler/test/beam_doc_SUITE.erl | 28 +++++++++++++++++--
.../beam_doc_SUITE_data/cover_compiled.erl | 7 +++++
lib/kernel/src/code.erl | 7 +++++
3 files changed, 40 insertions(+), 2 deletions(-)
create mode 100644 lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl
diff --git a/lib/compiler/test/beam_doc_SUITE.erl b/lib/compiler/test/beam_doc_SUITE.erl
index 2ce2a56075..25b482b370 100644
--- a/lib/compiler/test/beam_doc_SUITE.erl
+++ b/lib/compiler/test/beam_doc_SUITE.erl
@@ -7,7 +7,8 @@
types_and_opaques/1, callback/1, hide_moduledoc2/1,
private_types/1, export_all/1, equiv/1, spec/1, deprecated/1, warn_missing_doc/1,
doc_with_file/1, doc_with_file_error/1, all_string_formats/1,
- docs_from_ast/1, spec_switch_order/1, user_defined_type/1, skip_doc/1]).
+ docs_from_ast/1, spec_switch_order/1, user_defined_type/1, skip_doc/1,
+ cover_compiled/1]).
-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/eep48.hrl").
@@ -16,7 +17,9 @@
-define(get_name(), atom_to_list(?FUNCTION_NAME)).
all() ->
- [{group, documentation_generation_tests}, doc_with_file].
+ [{group, documentation_generation_tests},
+ doc_with_file,
+ cover_compiled].
groups() ->
[{documentation_generation_tests, [parallel], documentation_generation_tests()}].
@@ -621,6 +624,27 @@ docs_from_ast(_Conf) ->
check_no_doc_attributes(BeamCodeWSource),
ok.
+cover_compiled(Config) ->
+ case test_server:is_cover() of
+ true ->
+ {skip, "Cover is running"};
+ false ->
+ try
+ DataDir = proplists:get_value(data_dir, Config),
+ ok = file:set_cwd(DataDir),
+
+ ModuleName = ?get_name(),
+ {ok, ModName} = default_compile_file(Config, ModuleName),
+ {ok, cover_compiled} = cover:compile(ModuleName),
+
+ {ok, #docs_v1{}} = code:get_doc(ModName),
+
+ ok
+ after
+ cover:stop()
+ end
+ end.
+
scan_and_parse(Code) ->
{ok, Toks, _} = erl_scan:string(Code),
parse(Toks).
diff --git a/lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl b/lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl
new file mode 100644
index 0000000000..94836996da
--- /dev/null
+++ b/lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl
@@ -0,0 +1,7 @@
+-module(cover_compiled).
+-moduledoc ~"""
+cover_compiled
+""".
+
+% SPDX-License-Identifier: Apache-2.0
+% SPDX-FileCopyrightText: 2025 Erlang/OTP and contributors
diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl
index 13a6fe37c6..831360c030 100644
--- a/lib/kernel/src/code.erl
+++ b/lib/kernel/src/code.erl
@@ -1867,6 +1867,13 @@ get_doc(Mod, #{sources:=[Source|Sources]}=Options) ->
Fn = filename:join([ErtsEbinDir, atom_to_list(Mod) ++ ".beam"]),
GetDoc(Fn)
end;
+ cover_compiled ->
+ case which(Mod, get_path()) of
+ non_existing ->
+ {error, missing};
+ Fn when is_list(Fn) ->
+ GetDoc(Fn)
+ end;
Error when is_atom(Error) ->
{error, Error};
Fn ->
--
2.43.0