File 2535-erl_lint-Add-support-for-deprecated_callback.patch of Package erlang

From b40860749488308d6f3ad6e1c431e797696d0969 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Mon, 4 Mar 2024 08:49:06 +0100
Subject: [PATCH 5/6] erl_lint: Add support for deprecated_callback

---
 bootstrap/lib/stdlib/ebin/otp_internal.beam | Bin 6224 -> 7252 bytes
 lib/stdlib/scripts/update_deprecations      |  16 +++++++-
 lib/stdlib/src/erl_lint.erl                 |  41 +++++++++++++++++++-
 lib/stdlib/src/otp_internal.erl             |  11 ++++++
 lib/stdlib/src/otp_internal.hrl             |   5 ++-
 lib/stdlib/test/erl_lint_SUITE.erl          |  13 +++++--
 6 files changed, 77 insertions(+), 9 deletions(-)

diff --git a/lib/stdlib/scripts/update_deprecations b/lib/stdlib/scripts/update_deprecations
index bf55d537c8..24de61076e 100755
--- a/lib/stdlib/scripts/update_deprecations
+++ b/lib/stdlib/scripts/update_deprecations
@@ -29,6 +29,7 @@
 -record(st,
         {functions = [],
          types = [],
+         callbacks = [],
          deprecations = #{}}).
 
 main(["update",Top]) ->
@@ -92,6 +93,14 @@ summarize_attributes([{removed_type, Rs} | As], Module, Acc0) ->
     Ts = sa_1(Rs, removed, Module, Acc0#st.types),
     Acc = Acc0#st{ types = Ts },
     summarize_attributes(As, Module, Acc);
+summarize_attributes([{deprecated_callback, Ds} | As], Module, Acc0) ->
+    Ts = sa_1(Ds, deprecated, Module, Acc0#st.callbacks),
+    Acc = Acc0#st{ callbacks = Ts },
+    summarize_attributes(As, Module, Acc);
+summarize_attributes([{removed_callback, Rs} | As], Module, Acc0) ->
+    Ts = sa_1(Rs, removed, Module, Acc0#st.callbacks),
+    Acc = Acc0#st{ callbacks = Ts },
+    summarize_attributes(As, Module, Acc);
 summarize_attributes([_ | As], Module, Acc) ->
     summarize_attributes(As, Module, Acc);
 summarize_attributes([], _Module, Acc) ->
@@ -108,7 +117,7 @@ sa_1([], _Tag, _Module, Acc) ->
 
 %%
 
-emit(Top, #st{ functions = Fs0, types = Ts, deprecations = Depr }) ->
+emit(Top, #st{ functions = Fs0, types = Ts, callbacks = Cs, deprecations = Depr }) ->
     Fs = insert_removals(Fs0, Depr),
     Name = filename:join(Top, "lib/stdlib/src/otp_internal.erl"),
     Contents = ["%%\n"
@@ -122,8 +131,10 @@ emit(Top, #st{ functions = Fs0, types = Ts, deprecations = Depr }) ->
                 "%%\n"
                 "%%    -deprecated([{foo,1,\"use bar/1 instead\"}]).\n"
                 "%%    -deprecated_type([{gadget,1,\"use widget/1 instead\"}]).\n"
+                "%%    -deprecated_callback([{gadget,1,\"use widget/1 instead\"}]).\n"
                 "%%    -removed([{hello,2,\"use there/2 instead\"}]).\n"
                 "%%    -removed_type([{frobnitz,1,\"use grunka/1 instead\"}]).\n"
+                "%%    -removed_callback([{frobnitz,1,\"use grunka/1 instead\"}]).\n"
                 "%%\n"
                 "%% Descriptions cannot be given with the `f/1` shorthand, and\n"
                 "%% it will fall back to a generic description referring the\n"
@@ -137,7 +148,8 @@ emit(Top, #st{ functions = Fs0, types = Ts, deprecations = Depr }) ->
                 "-include(\"otp_internal.hrl\").\n"
                 "%%\n",
                 emit_function("obsolete", Fs),
-                emit_function("obsolete_type", Ts)],
+                emit_function("obsolete_type", Ts),
+                emit_function("obsolete_callback", Cs)],
     ok = file:write_file(Name, Contents),
     ok.
 
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 4450b87a2d..1a8bad2d8a 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -370,6 +370,8 @@ format_error({removed, MFA, String}) when is_list(String) ->
     io_lib:format("~s is removed; ~s", [format_mfa(MFA), String]);
 format_error({removed_type, MNA, String}) ->
     io_lib:format("the type ~s is removed; ~s", [format_mna(MNA), String]);
+format_error({removed_callback, MNA, String}) ->
+    io_lib:format("the callback ~s is removed; ~s", [format_mna(MNA), String]);
 format_error({obsolete_guard, {F, A}}) ->
     io_lib:format("~p/~p obsolete (use is_~p/~p)", [F, A, F, A]);
 format_error({obsolete_guard_overridden,Test}) ->
@@ -749,6 +751,9 @@ start(File, Opts) ->
 	 {deprecated_type,
 	  bool_option(warn_deprecated_type, nowarn_deprecated_type,
 		      true, Opts)},
+	 {deprecated_callback,
+	  bool_option(warn_deprecated_callback, nowarn_deprecated_callback,
+		      true, Opts)},
          {obsolete_guard,
           bool_option(warn_obsolete_guard, nowarn_obsolete_guard,
                       true, Opts)},
@@ -1202,7 +1207,7 @@ check_behaviour(St0) ->
 
 behaviour_check(Bs, St0) ->
     {AllBfs0, St1} = all_behaviour_callbacks(Bs, [], St0),
-    St = behaviour_missing_callbacks(AllBfs0, St1),
+    St2 = behaviour_missing_callbacks(AllBfs0, St1),
     Exports = exports(St0),
     F = fun(Bfs, OBfs) ->
                 [B || B <- Bfs,
@@ -1211,7 +1216,8 @@ behaviour_check(Bs, St0) ->
         end,
     %% After fixing missing callbacks new warnings may be emitted.
     AllBfs = [{Item,F(Bfs0, OBfs0)} || {Item,Bfs0,OBfs0} <- AllBfs0],
-    behaviour_conflicting(AllBfs, St).
+    St3 = behaviour_conflicting(AllBfs, St2),
+    behaviour_deprecated(AllBfs0, Exports, St3).
 
 all_behaviour_callbacks([{Anno,B}|Bs], Acc, St0) ->
     {Bfs0,OBfs0,St} = behaviour_callbacks(Anno, B, St0),
@@ -1257,6 +1263,37 @@ behaviour_callbacks(Anno, B, St0) ->
             {[], [], St2}
     end.
 
+behaviour_deprecated([{{Anno, B}, Bfs, _OBfs} | T], Exports, St) ->
+    behaviour_deprecated(T, Exports, 
+                         behaviour_deprecated(Anno, B, Bfs, Exports, St));
+behaviour_deprecated([], _Exports, St) ->
+    St.
+
+-dialyzer({no_match, behaviour_deprecated/5}).
+
+behaviour_deprecated(Anno, B, [{F, A} | T], Exports, St0) ->
+    St =
+        case gb_sets:is_member({F,A}, Exports) of
+            false -> St0;
+            true ->
+                case otp_internal:obsolete_callback(B, F, A) of
+                    {deprecated, String} when is_list(String) ->
+                        case is_warn_enabled(deprecated_callback, St0) of
+                            true ->
+                                add_warning(Anno, {deprecated_callback, {B, F, A}, String}, St0);
+                            false ->
+                                St0
+                        end;
+                    {removed, String} ->
+                        add_warning(Anno, {removed_callback, {B, F, A}, String}, St0);
+                    no ->
+                        St0
+                end
+        end,
+    behaviour_deprecated(Anno, B, T, Exports, St);
+behaviour_deprecated(_Anno, _B, [], _Exports, St) ->
+    St.
+
 behaviour_missing_callbacks([{{Anno,B},Bfs0,OBfs}|T], St0) ->
     Bfs = ordsets:subtract(ordsets:from_list(Bfs0), ordsets:from_list(OBfs)),
     Exports = gb_sets:to_list(exports(St0)),
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 764896edd4..3c880daf51 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -9,8 +9,10 @@
 %%
 %%    -deprecated([{foo,1,"use bar/1 instead"}]).
 %%    -deprecated_type([{gadget,1,"use widget/1 instead"}]).
+%%    -deprecated_callback([{gadget,1,"use widget/1 instead"}]).
 %%    -removed([{hello,2,"use there/2 instead"}]).
 %%    -removed_type([{frobnitz,1,"use grunka/1 instead"}]).
+%%    -removed_callback([{frobnitz,1,"use grunka/1 instead"}]).
 %%
 %% Descriptions cannot be given with the `f/1` shorthand, and
 %% it will fall back to a generic description referring the
@@ -293,3 +295,12 @@ obsolete_type(http_uri, user_info, 0) ->
     {removed, "use uri_string instead"};
 obsolete_type(_,_,_) -> no.
 
+-dialyzer({no_match, obsolete_callback/3}).
+obsolete_callback(gen_event, format_status, 2) ->
+    {deprecated, "use format_status/1 instead"};
+obsolete_callback(gen_server, format_status, 2) ->
+    {deprecated, "use format_status/1 instead"};
+obsolete_callback(gen_statem, format_status, 2) ->
+    {deprecated, "use format_status/1 instead"};
+obsolete_callback(_,_,_) -> no.
+
diff --git a/lib/stdlib/src/otp_internal.hrl b/lib/stdlib/src/otp_internal.hrl
index 17e15da68f..1d4923111d 100644
--- a/lib/stdlib/src/otp_internal.hrl
+++ b/lib/stdlib/src/otp_internal.hrl
@@ -23,7 +23,7 @@
 %% auto-generated by stdlib/scripts/update_deprecations
 %%
 
--export([obsolete/3, obsolete_type/3]).
+-export([obsolete/3, obsolete_type/3, obsolete_callback/3]).
 
 -type tag()     :: 'deprecated' | 'removed'. %% | 'experimental'.
 -type mfas()    :: mfa() | {atom(), atom(), [byte()]} | string().
@@ -34,3 +34,6 @@
 
 -spec obsolete_type(module(), atom(), arity()) ->
         'no' | {tag(), string()} | {tag(), mfas(), release()}.
+
+-spec obsolete_callback(module(), atom(), arity()) ->
+        'no' | {tag(), string()} | {tag(), mfas(), release()}.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 5c5365fd62..588c7234cf 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -3677,23 +3677,28 @@ otp_11861(Conf) when is_list(Conf) ->
               terminate(_, _) -> ok.
              ">>,
            [],
+           %% Nothing...
            []},
           {otp_11861_9,
            <<"
               -behaviour(gen_server).
               -export([handle_call/3,handle_cast/2,handle_info/2,
-                       code_change/3, init/1, terminate/2, format_status/2]).
+                       code_change/3, init/1, terminate/2,
+                       format_status/1, format_status/2]).
               handle_call(_, _, _) -> ok.
               handle_cast(_, _) -> ok.
               handle_info(_, _) -> ok.
               code_change(_, _, _) -> ok.
               init(_) -> ok.
               terminate(_, _) -> ok.
-              format_status(_, _) -> ok. % optional callback
+              format_status(_) -> ok. % optional callback
+              format_status(_, _) -> ok. % deprecated optional callback
              ">>,
            [],
-           %% Nothing...
-           []},
+           {warnings,[{{2,16},
+                       erl_lint,
+                       {deprecated_callback,{gen_server,format_status,2},
+                        "use format_status/1 instead"}}]}},
           {otp_11861_10,
            <<"
               -optional_callbacks([{b1,1,bad}]). % badly formed and ignored
-- 
2.35.3

openSUSE Build Service is sponsored by