Skip to content

Commit

Permalink
kernel: Fix code:get_doc/1,2 when cover_compiled
Browse files Browse the repository at this point in the history
  • Loading branch information
williamthome committed Feb 25, 2025
1 parent 53e6751 commit d51a975
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 2 deletions.
18 changes: 16 additions & 2 deletions lib/compiler/test/beam_doc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@
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,
no_doc_attributes/1, converted_metadata/1, converted_metadata_warnings/1]).
no_doc_attributes/1, converted_metadata/1, converted_metadata_warnings/1,
cover_compiled/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/eep48.hrl").
Expand Down Expand Up @@ -55,7 +56,8 @@ documentation_generation_tests() ->
skip_doc,
no_doc_attributes,
converted_metadata,
converted_metadata_warnings
converted_metadata_warnings,
cover_compiled
].

singleton_moduledoc(Conf) ->
Expand Down Expand Up @@ -694,6 +696,18 @@ converted_metadata_warnings(Config) ->

ok.

cover_compiled(Config) ->
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.

scan_and_parse(Code) ->
{ok, Toks, _} = erl_scan:string(Code),
parse(Toks).
Expand Down
7 changes: 7 additions & 0 deletions lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
-module(cover_compiled).
-moduledoc ~"""
cover_compiled
""".

% SPDX-License-Identifier: Apache-2.0
% SPDX-FileCopyrightText: 2025 Erlang/OTP and contributors
9 changes: 9 additions & 0 deletions lib/kernel/src/code.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1867,6 +1867,15 @@ get_doc(Mod, #{sources:=[Source|Sources]}=Options) ->
ErtsDir ->
GetDoc(filename:join([ErtsDir, "ebin", atom_to_list(Mod) ++ ".beam"]))
end;
cover_compiled ->
case which(Mod, get_path()) of
non_existing ->
{error, missing};
Error when is_atom(Error) ->
{error, Error};
Fn when is_list(Fn) ->
GetDoc(Fn)
end;
Error when is_atom(Error) ->
{error, Error};
Fn ->
Expand Down

0 comments on commit d51a975

Please sign in to comment.