File 1501-Add-source-and-behaviour-information-to-docs-chunk-m.patch of Package erlang
From cb94f4d61cbff3f8453310036e9263b5c77f16dc Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jonatan=20K=C5=82osko?= <jonatanklosko@gmail.com>
Date: Tue, 22 Oct 2024 21:57:29 +0800
Subject: [PATCH] Add source and behaviour information to docs chunk metadata
---
lib/compiler/src/beam_doc.erl | 52 +++++++++++-----
lib/compiler/test/beam_doc_SUITE.erl | 62 ++++++++++++-------
.../test/beam_doc_SUITE_data/behaviours.erl | 10 +++
.../source_annotations.erl | 19 ++++++
.../test/beam_doc_SUITE_data/source_path.erl | 7 +++
5 files changed, 115 insertions(+), 35 deletions(-)
create mode 100644 lib/compiler/test/beam_doc_SUITE_data/behaviours.erl
create mode 100644 lib/compiler/test/beam_doc_SUITE_data/source_annotations.erl
create mode 100644 lib/compiler/test/beam_doc_SUITE_data/source_path.erl
diff --git a/lib/compiler/src/beam_doc.erl b/lib/compiler/src/beam_doc.erl
index a9a9d31abc..1bcab41904 100644
--- a/lib/compiler/src/beam_doc.erl
+++ b/lib/compiler/src/beam_doc.erl
@@ -57,12 +57,15 @@
opts :: [opt()],
module :: module(),
+ anno = none :: none | erl_anno:anno(),
deprecated = #{} :: map(),
docformat = ?DEFAULT_FORMAT :: binary(),
moduledoc = {?DEFAULT_MODULE_DOC_LOC, none} :: {integer() | erl_anno:anno(), none | map() | hidden},
moduledoc_meta = none :: none | #{ _ := _ },
+ behaviours = [] :: list(module()),
+
%% If the module has any documentation attributes at all.
%% If it does not and no documentation related options are
%% passed, then we don't generate a doc chunk.
@@ -244,10 +247,15 @@ main(Dirname, Filename, AST, CmdLineOpts) ->
if State1#docs.has_docs orelse Opts =/= [] ->
Docs = extract_documentation(AST, State1),
{ModuleDocAnno, ModuleDoc} = Docs#docs.moduledoc,
+ Behaviours = lists:sort(Docs#docs.behaviours),
+ Metadata0 = maps:merge(Docs#docs.moduledoc_meta, #{
+ source_anno => Docs#docs.anno,
+ behaviours => Behaviours}),
+ Metadata = maybe_add_source_path_meta(Metadata0, Docs, CmdLineOpts),
DocV1 = #docs_v1{},
Result = DocV1#docs_v1{ format = Docs#docs.docformat,
anno = ModuleDocAnno,
- metadata = Docs#docs.moduledoc_meta,
+ metadata = Metadata,
module_doc = ModuleDoc,
docs = process_docs(Docs) },
{ok, Result, Docs#docs.warnings };
@@ -255,6 +263,16 @@ main(Dirname, Filename, AST, CmdLineOpts) ->
{error, no_docs}
end.
+maybe_add_source_path_meta(Metadata, Docs, CmdLineOpts) ->
+ case lists:member(deterministic, CmdLineOpts) of
+ true ->
+ Metadata;
+ false ->
+ Dir = filename:absname(Docs#docs.cwd),
+ SourcePath = filename:join(Dir, Docs#docs.filename),
+ Metadata#{source_path => SourcePath}
+ end.
+
extract_opts(AST, CmdLineOpts) ->
CompileOpts = lists:flatten([C || {attribute,_,compile,C} <- AST]),
NormalizedOpts = normalize_warn_missing_doc(CmdLineOpts ++ CompileOpts),
@@ -321,6 +339,7 @@ preprocessing(AST, State) ->
fun extract_exported_funs/2,
fun extract_file/2,
fun extract_record/2,
+ fun extract_behaviours/2,
fun extract_hidden_types0/2,
fun extract_type_defs0/2,
fun extract_type_dependencies/2],
@@ -363,8 +382,8 @@ extract_deprecated(_, State) ->
extract_exported_types0({attribute,_ANNO,export_type,ExportedTypes}, State) ->
update_export_types(State, ExportedTypes);
-extract_exported_types0({attribute,_ANNO,module, Module}, State) ->
- State#docs{ module = Module };
+extract_exported_types0({attribute,Anno,module, Module}, State) ->
+ State#docs{ module = Module, anno = Anno };
extract_exported_types0({attribute,_ANNO,compile, export_all}, State) ->
update_export_all(State, true);
extract_exported_types0(_AST, State) ->
@@ -437,27 +456,27 @@ track_documentation({attribute, Anno, doc, Doc}, State) when is_binary(Doc) ->
track_documentation(_, State) ->
State.
-upsert_documentation_from_terminal_item({function, _Anno, F, Arity, _}, State) ->
- upsert_documentation(function, F, Arity, State);
-upsert_documentation_from_terminal_item({attribute, _Anno, TypeOrOpaque, {TypeName, _TypeDef, TypeArgs}},State)
+upsert_documentation_from_terminal_item({function, Anno, F, Arity, _}, State) ->
+ upsert_documentation(function, F, Arity, Anno, State);
+upsert_documentation_from_terminal_item({attribute, Anno, TypeOrOpaque, {TypeName, _TypeDef, TypeArgs}},State)
when TypeOrOpaque =:= type; TypeOrOpaque =:= opaque ->
Arity = length(fun_to_varargs(TypeArgs)),
- upsert_documentation(type, TypeName, Arity, State);
-upsert_documentation_from_terminal_item({attribute, _Anno, callback, {{CB, Arity}, _Form}}, State) ->
- upsert_documentation(callback, CB, Arity, State);
+ upsert_documentation(type, TypeName, Arity, Anno, State);
+upsert_documentation_from_terminal_item({attribute, Anno, callback, {{CB, Arity}, _Form}}, State) ->
+ upsert_documentation(callback, CB, Arity, Anno, State);
upsert_documentation_from_terminal_item(_, State) ->
State.
-upsert_documentation(Tag, Name, Arity, State) when Tag =:= function;
- Tag =:= type;
- Tag =:= opaque;
- Tag =:= callback ->
+upsert_documentation(Tag, Name, Arity, Anno, State) when Tag =:= function;
+ Tag =:= type;
+ Tag =:= opaque;
+ Tag =:= callback ->
Docs = State#docs.docs,
State1 = case maps:get({Tag, Name, Arity}, Docs, none) of
none ->
Status = State#docs.doc_status,
Doc = State#docs.doc,
- Meta = State#docs.meta,
+ Meta = (State#docs.meta)#{source_anno => Anno},
State#docs{docs = Docs#{{Tag, Name, Arity} => {Status, Doc, Meta}}};
{Status, Documentation, Meta} ->
Status1 = upsert_state(Status, State#docs.doc_status),
@@ -539,6 +558,11 @@ extract_record({attribute, Anno, record, {Name, Fields}}, State) ->
extract_record(_, State) ->
State.
+extract_behaviours({attribute, _Anno, behaviour, Behaviour}, State) ->
+ State#docs{ behaviours = [Behaviour | State#docs.behaviours] };
+extract_behaviours(_, State) ->
+ State.
+
%%
%% Extracts types with documentation attribute set to `hidden` or `false`.
%%
diff --git a/lib/compiler/test/beam_doc_SUITE.erl b/lib/compiler/test/beam_doc_SUITE.erl
index f347274efc..6135fe09fa 100644
--- a/lib/compiler/test/beam_doc_SUITE.erl
+++ b/lib/compiler/test/beam_doc_SUITE.erl
@@ -2,7 +2,7 @@
-module(beam_doc_SUITE).
-export([all/0, groups/0, init_per_group/2, end_per_group/2, singleton_moduledoc/1, singleton_doc/1,
docmodule_with_doc_attributes/1, hide_moduledoc/1, docformat/1,
- singleton_docformat/1, singleton_meta/1, slogan/1,
+ singleton_docformat/1, singleton_meta/1, source_path/1, behaviours/1, slogan/1,
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,
@@ -36,6 +36,8 @@ documentation_generation_tests() ->
docformat,
singleton_docformat,
singleton_meta,
+ source_path,
+ behaviours,
slogan,
types_and_opaques,
callback,
@@ -125,40 +127,57 @@ hide_moduledoc2(Conf) ->
docformat(Conf) ->
{ok, ModName} = default_compile_file(Conf, "docformat"),
ModuleDoc = #{<<"en">> => <<"Moduledoc test module">>},
- Meta = #{format => "text/asciidoc",
- deprecated => "Use something else",
- otp_doc_vsn => {1,0,0},
- since => "1.0"},
Doc = #{<<"en">> => <<"Doc test module">>},
{ok, {docs_v1, _,_, <<"text/asciidoc">>, ModuleDoc, Meta,
[{{function, main,_},_, _, Doc, _}]}} = code:get_doc(ModName),
+ #{format := "text/asciidoc", deprecated := "Use something else", otp_doc_vsn := {1,0,0}, since := "1.0"} = Meta,
ok.
singleton_docformat(Conf) ->
{ok, ModName} = default_compile_file(Conf, "singleton_docformat"),
ModuleDoc = #{<<"en">> => <<"Moduledoc test module">>},
- Meta = #{format => <<"text/asciidoc">>,
- deprecated => ~"Use something else",
- otp_doc_vsn => {1,0,0},
- since => ~"1.0"},
Doc = #{<<"en">> => <<"Doc test module\n\nMore info here">>},
- FunMeta = #{ authors => [<<"Beep Bop">>], equiv => <<"main/3">>, since => ~"1.0" },
{ok, {docs_v1, _,erlang, <<"text/asciidoc">>, ModuleDoc, Meta,
[{{function, main,0},_, [<<"main()">>], Doc, FunMeta}]}} = code:get_doc(ModName),
+ #{format := <<"text/asciidoc">>,
+ deprecated := ~"Use something else",
+ otp_doc_vsn := {1,0,0},
+ since := ~"1.0"} = Meta,
+ #{authors := [<<"Beep Bop">>], equiv := <<"main/3">>, since := ~"1.0"} = FunMeta,
ok.
singleton_meta(Conf) ->
ModuleName = ?get_name(),
{ok, ModName} = default_compile_file(Conf, ModuleName),
- Meta = #{ authors => [<<"Beep Bop">>], equiv => <<"main/3">>, since => ~"1.0" },
DocMain1 = #{<<"en">> => <<"Returns always ok.">>},
- {ok, {docs_v1, _,erlang, <<"text/markdown">>, none, #{ since := ~"1.0" },
+ Meta = #{authors => [<<"Beep Bop">>], equiv => <<"main/3">>, since => ~"1.0", source_anno => {9, 1}},
+ {ok, {docs_v1, _,erlang, <<"text/markdown">>, none, #{ since := ~"1.0", source_anno := {1, 2} },
[{{function, main1,0},_, [<<"main1()">>], DocMain1, #{equiv := <<"main(_)">>,
- since := ~"1.1"}},
+ since := ~"1.1",
+ source_anno := {19, 1}}},
{{function, main,0},_, [<<"main()">>], none, Meta}]}}
= code:get_doc(ModName),
ok.
+source_path(Conf) ->
+ ModuleName = ?get_name(),
+ % Includes absolute source path by default
+ FilePath = filename:absname(data_file_path(Conf, ModuleName)),
+ {ok, ModName} = default_compile_file(Conf, ModuleName),
+ {ok, {docs_v1, _, _, _, _, Meta1, _}} = code:get_doc(ModName),
+ #{source_path := FilePath} = Meta1,
+ % Excludes source path when deterministic
+ {ok, ModName} = default_compile_file(Conf, ModuleName, [deterministic]),
+ {ok, {docs_v1, _, _, _, _, Meta2, _}} = code:get_doc(ModName),
+ false = is_map_key(source_path, Meta2),
+ ok.
+
+behaviours(Conf) ->
+ ModuleName = ?get_name(),
+ {ok, ModName} = default_compile_file(Conf, ModuleName),
+ {ok, {docs_v1, _, _, _, _, #{behaviours := [gen_event, gen_server]}, _}} = code:get_doc(ModName),
+ ok.
+
slogan(Conf) ->
ModuleName = ?get_name(),
{ok, ModName} = default_compile_file(Conf, ModuleName),
@@ -189,8 +208,6 @@ types_and_opaques(Conf) ->
OpaqueDoc = #{<<"en">> =>
<<"Represents the name of a person that cannot be named.">>},
MaybeOpaqueDoc = #{<<"en">> => <<"mmaybe(X) ::= nothing | X.\n\nRepresents a maybe type.">>},
- MaybeMeta = #{ authors => "Someone else", exported => true },
- NaturalNumberMeta = #{since => "1.0", equiv => <<"non_neg_integer/0">>, exported => true},
{ok, {docs_v1, _,_, _, none, _,
[%% Type Definitions
@@ -202,7 +219,7 @@ types_and_opaques(Conf) ->
UsesPublic, Ignore, MapFun, PrivateEncoding, Foo
]}} = code:get_doc(ModName),
- {{type,public,0},{125,2},[<<"public()">>],none,#{exported := true}} = Public,
+ {{type,public,0},{125,2},[<<"public()">>],none,#{exported := true, source_anno := {125, 2}}} = Public,
{{type,intermediate,0},{124,2},[<<"intermediate()">>],none,#{exported := false}} = Intermediate,
{{type,hidden_nowarn_type,0},{120,2},[<<"hidden_nowarn_type()">>],hidden,#{exported := false}} = HiddenNoWarnType,
{{type,hidden_type,0},{117,2},[<<"hidden_type()">>],hidden,#{exported := false}} = HiddenType,
@@ -222,12 +239,12 @@ types_and_opaques(Conf) ->
{{type,hidden,0},_,[<<"hidden()">>],hidden,#{exported := true}} = Hidden,
{{type,hidden_false,0},_,[<<"hidden_false()">>],hidden,
#{exported := true, authors := "Someone else"}} = HiddenFalse,
- {{type, mmaybe,1},_,[<<"mmaybe(X)">>], MaybeOpaqueDoc, MaybeMeta} = MMaybe,
+ {{type, mmaybe,1},_,[<<"mmaybe(X)">>], MaybeOpaqueDoc, #{authors := "Someone else", exported := true}} = MMaybe,
{{type, unnamed,0},{30,2},[<<"unnamed()">>], OpaqueDoc,
#{equiv := <<"non_neg_integer()">>, exported := true}} = Unnamed,
{{type, param,1},_,[<<"param(X)">>], GenericsDoc,
#{equiv := <<"madeup()">>, exported := true}} = Param,
- {{type, natural_number,0},_,[<<"natural_number()">>], none, NaturalNumberMeta} = NatNumber,
+ {{type, natural_number,0},_,[<<"natural_number()">>], none, #{since := "1.0", equiv := <<"non_neg_integer/0">>, exported := true}} = NatNumber,
{{type, name,1},_,[<<"name(_)">>], TypeDoc, #{exported := true}} = Name,
{{type, hidden_included_type, 0}, _, _, hidden, #{exported := false }} = HiddenIncludedType,
@@ -267,7 +284,7 @@ callback(Conf) ->
FunctionDoc = #{<<"en">> => <<"all_ok()\n\nCalls all_ok/0">>},
ChangeOrder = #{<<"en">> => <<"Test changing order">>},
{ok, {docs_v1, _,_, _, none, _,
- [{{callback,nowarn,1},{39,2},[<<"nowarn(Arg)">>],hidden,#{}},
+ [{{callback,nowarn,1},{39,2},[<<"nowarn(Arg)">>],hidden,#{source_anno := {41, 2}}},
{{callback,warn,0},{36,2},[<<"warn()">>],hidden,#{}},
{{callback,bounded,1},_,[<<"bounded(X)">>],none,#{}},
{{callback,multi,1},_,[<<"multi(Argument)">>],
@@ -632,8 +649,7 @@ parse(Toks) ->
[F | parse(Rest)].
compile_file(Conf, ModuleName, ExtraOpts) ->
- ErlModName = ModuleName ++ ".erl",
- Filename = filename:join(proplists:get_value(data_dir, Conf), ErlModName),
+ Filename = data_file_path(Conf, ModuleName),
io:format("Compiling: ~ts~n~p~n",[Filename, ExtraOpts]),
case compile:file(Filename, ExtraOpts) of
Res when element(1, Res) =:= ok ->
@@ -649,6 +665,10 @@ compile_file(Conf, ModuleName, ExtraOpts) ->
Else
end.
+data_file_path(Conf, ModuleName) ->
+ ErlModName = ModuleName ++ ".erl",
+ filename:join(proplists:get_value(data_dir, Conf), ErlModName).
+
default_compile_file(Conf, ModuleName) ->
default_compile_file(Conf, ModuleName, []).
default_compile_file(Conf, ModuleName, ExtraOpts) ->
diff --git a/lib/compiler/test/beam_doc_SUITE_data/behaviours.erl b/lib/compiler/test/beam_doc_SUITE_data/behaviours.erl
new file mode 100644
index 0000000000..4c5de47fb3
--- /dev/null
+++ b/lib/compiler/test/beam_doc_SUITE_data/behaviours.erl
@@ -0,0 +1,10 @@
+-module(behaviours).
+
+-export([]).
+
+-behaviour(gen_server).
+-behaviour(gen_event).
+
+-moduledoc "
+Moduledoc test module
+".
diff --git a/lib/compiler/test/beam_doc_SUITE_data/source_annotations.erl b/lib/compiler/test/beam_doc_SUITE_data/source_annotations.erl
new file mode 100644
index 0000000000..9d59f10616
--- /dev/null
+++ b/lib/compiler/test/beam_doc_SUITE_data/source_annotations.erl
@@ -0,0 +1,19 @@
+-module(source_annotations).
+
+-export([main/1,
+ bar/0,
+ no_slogan/1,
+ spec_slogan/1,
+ spec_slogan/2,
+ no_doc_slogan/1,
+ spec_no_doc_slogan/1,
+ spec_multiclause_slogan_ignored/1,
+ connect/2
+ ]).
+
+-spec main(X :: integer()) -> ok.
+main(_X) ->
+ ok.
+
+bar() ->
+ ok.
diff --git a/lib/compiler/test/beam_doc_SUITE_data/source_path.erl b/lib/compiler/test/beam_doc_SUITE_data/source_path.erl
new file mode 100644
index 0000000000..0ca4df4665
--- /dev/null
+++ b/lib/compiler/test/beam_doc_SUITE_data/source_path.erl
@@ -0,0 +1,7 @@
+-module(source_path).
+
+-export([]).
+
+-moduledoc "
+Moduledoc test module
+".
--
2.43.0