File 5424-compiler-Add-doc-support-for-deprecate_callback.patch of Package erlang
From d21abaa2486479ec52b635c265270fe69f881648 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 28 Feb 2024 15:59:56 +0100
Subject: [PATCH 4/6] compiler: Add doc support for deprecate_callback
---
bootstrap/lib/compiler/ebin/beam_doc.beam | Bin 21636 -> 21752 bytes
bootstrap/lib/stdlib/ebin/erl_lint.beam | Bin 93472 -> 108092 bytes
lib/compiler/src/beam_doc.erl | 22 +++++++++++-------
lib/compiler/test/beam_doc_SUITE.erl | 9 ++++---
.../test/beam_doc_SUITE_data/deprecated.erl | 11 +++++++++
lib/stdlib/src/erl_lint.erl | 6 +++++
6 files changed, 37 insertions(+), 11 deletions(-)
diff --git a/lib/compiler/src/beam_doc.erl b/lib/compiler/src/beam_doc.erl
index f4c6ed46a9..d7635a78c4 100644
--- a/lib/compiler/src/beam_doc.erl
+++ b/lib/compiler/src/beam_doc.erl
@@ -335,15 +335,13 @@ preprocessing(AST, State) ->
end,
foldl(PreprocessingFuns, State, AST).
-extract_deprecated({attribute, Anno, deprecated, Deprecations}, State)
- when is_list(Deprecations) ->
+extract_deprecated({attribute, Anno, DeprecatedType, Deprecations}, State)
+ when is_list(Deprecations),
+ DeprecatedType =:= deprecated orelse
+ DeprecatedType =:= deprecated_type orelse
+ DeprecatedType =:= deprecated_callback ->
lists:foldl(fun(D, S) ->
- extract_deprecated({attribute, Anno, deprecated, D}, S)
- end, State, Deprecations);
-extract_deprecated({attribute, Anno, deprecated_type, Deprecations}, State)
- when is_list(Deprecations) ->
- lists:foldl(fun(D, S) ->
- extract_deprecated({attribute, Anno, deprecated_type, D}, S)
+ extract_deprecated({attribute, Anno, DeprecatedType, D}, S)
end, State, Deprecations);
extract_deprecated({attribute, Anno, deprecated, {F, A}}, State) ->
extract_deprecated({attribute, Anno, deprecated, {F, A, undefined}}, State);
@@ -355,6 +353,11 @@ extract_deprecated({attribute, Anno, deprecated_type, {F, A}}, State) ->
extract_deprecated({attribute, _, deprecated_type, {F, A, Reason}}, State) ->
Deprecations = (State#docs.deprecated)#{ {type, F, A} => Reason },
State#docs{ deprecated = Deprecations };
+extract_deprecated({attribute, Anno, deprecated_callback, {F, A}}, State) ->
+ extract_deprecated({attribute, Anno, deprecated_callback, {F, A, undefined}}, State);
+extract_deprecated({attribute, _, deprecated_callback, {F, A, Reason}}, State) ->
+ Deprecations = (State#docs.deprecated)#{ {callback, F, A} => Reason },
+ State#docs{ deprecated = Deprecations };
extract_deprecated(_, State) ->
State.
@@ -1029,6 +1032,9 @@ maybe_add_deprecation({Kind, Name, Arity}, Meta, #docs{ module = Module,
info_string(Value)});
Kind =:= type ->
erl_lint:format_error({deprecated_type, {Module,Name,Arity},
+ info_string(Value)});
+ Kind =:= callback ->
+ erl_lint:format_error({deprecated_callback, {Module,Name,Arity},
info_string(Value)})
end,
Meta#{ deprecated => unicode:characters_to_binary(Text) }
diff --git a/lib/compiler/test/beam_doc_SUITE.erl b/lib/compiler/test/beam_doc_SUITE.erl
index 3cf4a2bfb1..e0ca255bac 100644
--- a/lib/compiler/test/beam_doc_SUITE.erl
+++ b/lib/compiler/test/beam_doc_SUITE.erl
@@ -389,6 +389,7 @@ deprecated(Conf) ->
{ok, {docs_v1, _,_, _, none, _,
[{{type,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the type deprecated:test(_) is deprecated; Deprecation reason">>}},
{{type,test,0},_,[<<"test()">>],none,#{deprecated := <<"the type deprecated:test() is deprecated; see the documentation for details">>}},
+ {{callback,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the callback deprecated:test(_) is deprecated; Deprecation reason">>}},
{{callback,test,0},_,[<<"test()">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,2},_,[<<"test(N, M)">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"deprecated:test/1 is deprecated; Deprecation reason">>}},
@@ -396,10 +397,11 @@ deprecated(Conf) ->
code:get_doc(ModName),
{ok, ModName} = default_compile_file(Conf, ModuleName, [{d,'TEST_WILDCARD'},
- {d, 'REASON', next_major_release}]),
+ {d, 'REASON', next_major_release}]),
{ok, {docs_v1, _,_, _, none, _,
[{{type,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the type deprecated:test(_) is deprecated; see the documentation for details">>}},
{{type,test,0},_,[<<"test()">>],none,#{deprecated := <<"the type deprecated:test() is deprecated; see the documentation for details">>}},
+ {{callback,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the callback deprecated:test(_) is deprecated; will be removed in the next major release. See the documentation for details">>}},
{{callback,test,0},_,[<<"test()">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,2},_,[<<"test(N, M)">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"deprecated:test/1 is deprecated; will be removed in the next major release. See the documentation for details">>}},
@@ -407,11 +409,12 @@ deprecated(Conf) ->
code:get_doc(ModName),
{ok, ModName} = default_compile_file(Conf, ModuleName, [{d,'ALL_WILDCARD'},
- {d,'REASON',next_version},
- {d,'TREASON',eventually}]),
+ {d,'REASON',next_version},
+ {d,'TREASON',eventually}]),
{ok, {docs_v1, _,_, _, none, _,
[{{type,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the type deprecated:test(_) is deprecated; will be removed in a future release. See the documentation for details">>}},
{{type,test,0},_,[<<"test()">>],none,#{deprecated := <<"the type deprecated:test() is deprecated; see the documentation for details">>}},
+ {{callback,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"the callback deprecated:test(_) is deprecated; will be removed in the next version. See the documentation for details">>}},
{{callback,test,0},_,[<<"test()">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,2},_,[<<"test(N, M)">>],none,#{deprecated := <<"Meta reason">>}},
{{function,test,1},_,[<<"test(N)">>],none,#{deprecated := <<"deprecated:test/1 is deprecated; will be removed in the next version. See the documentation for details">>}},
diff --git a/lib/compiler/test/beam_doc_SUITE_data/deprecated.erl b/lib/compiler/test/beam_doc_SUITE_data/deprecated.erl
index 4a4147b46f..b2b993252d 100644
--- a/lib/compiler/test/beam_doc_SUITE_data/deprecated.erl
+++ b/lib/compiler/test/beam_doc_SUITE_data/deprecated.erl
@@ -11,9 +11,20 @@
-define(TREASON,"Deprecation reason").
-endif.
+-ifdef(TEST_WILDCARD).
+-deprecated_callback({test, '_', ?REASON}).
+-else.
+-ifdef(ALL_WILDCARD).
+-deprecated_callback({'_', '_', ?REASON}).
+-else.
+-deprecated_callback([{test, 1, ?REASON}]).
+-endif.
+-endif.
-doc #{ deprecated => "Meta reason" }.
-callback test() -> ok.
+-callback test(N) -> N.
+
-ifdef(TEST_WILDCARD).
-deprecated({test, '_', ?REASON}).
-else.
--
2.35.3