File 3341-Compile-time-no-longer-available.patch of Package erlang

From 45c4aeb09cde4026a0234642809d24477ce0b58d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?J=C3=A9r=C3=B4me=20de=20Bretagne?=
 <jerome.debretagne@gmail.com>
Date: Sun, 9 Jan 2022 00:38:05 +0100
Subject: [PATCH] Compile time no longer available

A few functions still attempted to extract the "compile time"
of each module. This info used to be available when calling
Module:module_info but was removed "a long time ago". A first
removal was done in OTP-15330 and this removes some remaining
leftover cases.
---
 lib/diameter/src/info/diameter_dbg.erl  | 18 +-----
 lib/diameter/src/info/diameter_info.erl | 83 +++----------------------
 lib/inets/src/inets_app/inets.erl       | 26 +++-----
 lib/megaco/src/app/megaco.erl           | 30 +++------
 lib/snmp/src/app/snmp.erl               | 20 +++---
 lib/stdlib/src/c.erl                    | 30 +--------
 6 files changed, 32 insertions(+), 175 deletions(-)

diff --git a/lib/diameter/src/info/diameter_dbg.erl b/lib/diameter/src/info/diameter_dbg.erl
index e1d2086871..718bbb582b 100644
--- a/lib/diameter/src/info/diameter_dbg.erl
+++ b/lib/diameter/src/info/diameter_dbg.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2022. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -30,9 +30,7 @@
          modules/0,
          versions/0,
          version_info/0,
-         compiled/0,
          procs/0,
-         latest/0,
          nl/0,
          sizes/0]).
 
@@ -164,13 +162,6 @@ versions() ->
 version_info() ->
     ?I:version_info(modules()).
 
-%% ----------------------------------------------------------
-%% # compiled/0
-%% ----------------------------------------------------------
-
-compiled() ->
-    ?I:compiled(modules()).
-
 %% ----------------------------------------------------------
 %% # procs/0
 %% ----------------------------------------------------------
@@ -178,13 +169,6 @@ compiled() ->
 procs() ->
     ?I:procs(?APP).
 
-%% ----------------------------------------------------------
-%% # latest/0
-%% ----------------------------------------------------------
-
-latest() ->
-    ?I:latest(modules()).
-
 %% ----------------------------------------------------------
 %% # nl/0
 %% ----------------------------------------------------------
diff --git a/lib/diameter/src/info/diameter_info.erl b/lib/diameter/src/info/diameter_info.erl
index 23a42e48fd..9ff6769ba5 100644
--- a/lib/diameter/src/info/diameter_info.erl
+++ b/lib/diameter/src/info/diameter_info.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 2010-2017. All Rights Reserved.
+%% Copyright Ericsson AB 2010-2022. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -40,9 +40,7 @@
          versions/1,
          version_info/1,
          attrs/2,
-         compiled/1,
          procs/1,
-         latest/1,
          list/1]).
 
 %% Support for rolling your own.
@@ -375,7 +373,7 @@ attr(Width, Mod, Attr, VFun) ->
     io:format(": ~*s~s~n", [-Width, Mod, attr(Mod, Attr, VFun)]).
 
 attr(Mod, Attr, VFun) ->
-    Key = key(Attr),
+    Key = attributes,
     try
         VFun(val(Attr, keyfetch(Attr, Mod:module_info(Key))))
     catch
@@ -383,44 +381,9 @@ attr(Mod, Attr, VFun) ->
             "-"
     end.
 
-attr(Mod, Attr) ->
-    attr(Mod, Attr, fun attr/1).
-
-key(time) -> compile;
-key(_)    -> attributes.
-
-val(time, {_,_,_,_,_,_} = T) ->
-    lists:flatten(io_lib:format("~p-~2..0B-~2..0B ~2..0B:~2..0B:~2..0B",
-                                tuple_to_list(T)));
 val(_, [V]) ->
     V.
 
-%%% ----------------------------------------------------------
-%%% # compiled(Modules|Prefix)
-%%%
-%%% Output: Number of modules listed.
-%%%
-%%% Description: List the compile times of the specified modules.
-%%% ----------------------------------------------------------
-
-compiled(Modules)
-  when is_list(Modules) ->
-    attrs(Modules, fun compiled/2);
-
-compiled(Prefix) ->
-    compiled(modules(Prefix)).
-
-compiled(Width, Mod) ->
-    io:format(": ~*s~19s  ~s~n", [-Width,
-                                  Mod,
-                                  attr(Mod, time),
-                                  opt(attr(Mod, date))]).
-
-opt("-") ->
-    "";
-opt(D) ->
-    "(" ++ D ++ ")".
-
 %%% ----------------------------------------------------------
 %%% # procs(Pred|Prefix|Prefixes|Pid|Pids)
 %%%
@@ -509,35 +472,6 @@ pre1(A, Pre) ->
 pre(A, Prefixes) ->
     lists:any(fun(P) -> pre1(A, atom_to_list(P)) end, Prefixes).
 
-%%% ----------------------------------------------------------
-%%% # latest(Modules|Prefix)
-%%%
-%%% Output: {Mod, {Y,M,D,HH,MM,SS}, Version}
-%%%
-%%% Description: Return the compile time of the most recently compiled
-%%%              module from the specified non-empty list. The modules
-%%%              are assumed to exist.
-%%% ----------------------------------------------------------
-
-latest(Prefix)
-  when is_atom(Prefix) ->
-    latest(modules(Prefix));
-
-latest([_|_] = Modules) ->
-    {Mod, T}
-        = hd(lists:sort(fun latest/2, lists:map(fun compile_time/1, Modules))),
-    {Mod, T, app_vsn(Mod)}.
-
-app_vsn(Mod) ->
-    keyfetch(app_vsn, Mod:module_info(attributes)).
-
-compile_time(Mod) ->
-    T = keyfetch(time, Mod:module_info(compile)),
-    {Mod, T}.
-
-latest({_,T1},{_,T2}) ->
-    T1 > T2.
-
 %%% ----------------------------------------------------------
 %%% version_info(Modules|Prefix)
 %%%
@@ -545,7 +479,7 @@ latest({_,T1},{_,T2}) ->
 %%%
 %%%         SysInfo = {Arch, Vers}
 %%%         OSInfo  = {Vers, {Fam, Name}}
-%%%         ModInfo = {Vsn, AppVsn, Time, CompilerVsn}
+%%%         ModInfo = {Vsn, AppVsn, CompilerVsn}
 %%% ----------------------------------------------------------
 
 version_info(Prefix)
@@ -560,8 +494,8 @@ mod_version_info(Mod) ->
     try
         Info = Mod:module_info(),
         [[Vsn], AppVsn] = get_values(attributes, [vsn, app_vsn], Info),
-        [Ver, Time] = get_values(compile, [version, time], Info),
-        [Vsn, AppVsn, Ver, Time]
+        [Ver] = get_values(compile, [version], Info),
+        [Vsn, AppVsn, Ver]
     catch
         _:_ ->
             []
@@ -600,15 +534,12 @@ print_mod_info(Mods) ->
 
 print_mod({Mod, []}) ->
     io:format("   ~w:~n", [Mod]);
-print_mod({Mod, [Vsn, AppVsn, Ver, {Year, Month, Day, Hour, Min, Sec}]}) ->
-    Time = io_lib:format("~w-~2..0w-~2..0w ~2..0w:~2..0w:~2..0w",
-                         [Year, Month, Day, Hour, Min, Sec]),
+print_mod({Mod, [Vsn, AppVsn, Ver]}) ->
     io:format("   ~w:~n"
               "      vsn      : ~s~n"
               "      app_vsn  : ~s~n"
-              "      compiled : ~s~n"
               "      compiler : ~s~n",
-              [Mod, str(Vsn), str(AppVsn), Time, Ver]).
+              [Mod, str(Vsn), str(AppVsn), Ver]).
 
 str(A)
   when is_atom(A) ->
diff --git a/lib/inets/src/inets_app/inets.erl b/lib/inets/src/inets_app/inets.erl
index b79accdaf2..99f3ba233c 100644
--- a/lib/inets/src/inets_app/inets.erl
+++ b/lib/inets/src/inets_app/inets.erl
@@ -1,8 +1,8 @@
 %%
 %% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 2006-2021. All Rights Reserved.
-%% 
+%%
+%% Copyright Ericsson AB 2006-2022. All Rights Reserved.
+%%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
 %% You may obtain a copy of the License at
@@ -14,7 +14,7 @@
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%% 
+%%
 %% %CopyrightEnd%
 %%
 %%
@@ -256,11 +256,9 @@ mod_version_info(Mod) ->
     {value, {app_vsn,    AppVsn}} = lists:keysearch(app_vsn,    1, Attr),
     {value, {compile,    Comp}}   = lists:keysearch(compile,    1, Info),
     {value, {version,    Ver}}    = lists:keysearch(version,    1, Comp),
-    {value, {time,       Time}}   = lists:keysearch(time,       1, Comp),
     {Mod, [{vsn,              Vsn},
            {app_vsn,          AppVsn},
-           {compiler_version, Ver},
-           {compile_time,     Time}]}.
+           {compiler_version, Ver}]}.
 
 sys_info() ->
     SysArch = string:strip(erlang:system_info(system_architecture),right,$\n),
@@ -328,22 +326,12 @@ print_mod_info({Module, Info}) ->
             _ ->
                 "Not found"
         end,
-    CompDate =
-        case key1search(compile_time, Info) of
-            {value, {Year, Month, Day, Hour, Min, Sec}} ->
-                lists:flatten(
-                  io_lib:format("~w-~2..0w-~2..0w ~2..0w:~2..0w:~2..0w",
-                                [Year, Month, Day, Hour, Min, Sec]));
-            _ ->
-                "Not found"
-        end,
     io:format("   ~w:~n"
               "      Vsn:          ~s~n"
               "      App vsn:      ~s~n"
               "      ASN.1 vsn:    ~s~n"
-              "      Compiler ver: ~s~n"
-              "      Compile time: ~s~n",
-              [Module, Vsn, AppVsn, Asn1Vsn, CompVer, CompDate]),
+              "      Compiler ver: ~s~n",
+              [Module, Vsn, AppVsn, Asn1Vsn, CompVer]),
     ok.
 
 
diff --git a/lib/megaco/src/app/megaco.erl b/lib/megaco/src/app/megaco.erl
index cfccd28c43..de6caaae3b 100644
--- a/lib/megaco/src/app/megaco.erl
+++ b/lib/megaco/src/app/megaco.erl
@@ -1,8 +1,8 @@
 %%
 %% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 1999-2020. All Rights Reserved.
-%% 
+%%
+%% Copyright Ericsson AB 1999-2022. All Rights Reserved.
+%%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
 %% You may obtain a copy of the License at
@@ -14,7 +14,7 @@
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%% 
+%%
 %% %CopyrightEnd%
 %%
 
@@ -623,25 +623,15 @@ print_mod_info({Module, Info}) ->
 	    _ ->
 		"Not found"
 	end,
-    CompDate = 
-	case key1search(compile_time, Info) of
-	    {value, {Year, Month, Day, Hour, Min, Sec}} ->
-		lists:flatten(
-		  io_lib:format("~w-~2..0w-~2..0w ~2..0w:~2..0w:~2..0w", 
-				[Year, Month, Day, Hour, Min, Sec]));
-	    _ ->
-		"Not found"
-	end,
     io:format("   ~w:~n"
 	      "      Vsn:          ~s~n"
 	      "      App vsn:      ~s~n"
 	      "      ASN.1 vsn:    ~s~n"
-	      "      Compiler ver: ~s~n"
-	      "      Compile time: ~s~n", 
-	      [Module, Vsn, AppVsn, Asn1Vsn, CompVer, CompDate]),
+	      "      Compiler ver: ~s~n",
+	      [Module, Vsn, AppVsn, Asn1Vsn, CompVer]),
     ok.
-    
-    
+
+
 
 key1search(Key, Vals) ->
     case lists:keysearch(Key, 1, Vals) of
@@ -691,11 +681,9 @@ mod_version_info(Mod) ->
     {value, {app_vsn,    AppVsn}} = lists:keysearch(app_vsn,    1, Attr),
     {value, {compile,    Comp}}   = lists:keysearch(compile,    1, Info),
     {value, {version,    Ver}}    = lists:keysearch(version,    1, Comp),
-    {value, {time,       Time}}   = lists:keysearch(time,       1, Comp),
     {Mod, [{vsn,              Vsn}, 
 	   {app_vsn,          AppVsn}, 
-	   {compiler_version, Ver}, 
-	   {compile_time,     Time}]}.
+	   {compiler_version, Ver}]}.
 
 sys_info() ->
     SysArch = string:strip(erlang:system_info(system_architecture),right,$\n),
diff --git a/lib/snmp/src/app/snmp.erl b/lib/snmp/src/app/snmp.erl
index 5781fad8ff..bc6a803eaa 100644
--- a/lib/snmp/src/app/snmp.erl
+++ b/lib/snmp/src/app/snmp.erl
@@ -1,8 +1,8 @@
-%% 
+%%
 %% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 1996-2020. All Rights Reserved.
-%% 
+%%
+%% Copyright Ericsson AB 1996-2022. All Rights Reserved.
+%%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
 %% You may obtain a copy of the License at
@@ -14,9 +14,9 @@
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%% 
+%%
 %% %CopyrightEnd%
-%% 
+%%
 -module(snmp).
 
 
@@ -608,13 +608,7 @@ mod_version_info(Mod) ->
 			 [{compiler_version, Ver}];
 		     not_found ->
 			 []
-		 end ++
-		     case key1search(time, Comp) of
-			 {value, Ver} ->
-			     [{compile_time, Ver}];
-			 not_found ->
-			     []
-		     end;
+		 end;
 	     not_found ->
 		 []
 	 end ++
diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl
index 605ca681d6..01b70f7f6a 100644
--- a/lib/stdlib/src/c.erl
+++ b/lib/stdlib/src/c.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2021. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2022. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -840,12 +840,9 @@ bi(I) ->
 m(M) ->
     L = M:module_info(),
     {exports,E} = lists:keyfind(exports, 1, L),
-    Time = get_compile_time(L),
     COpts = get_compile_options(L),
     format("Module: ~w~n", [M]),
     print_md5(L),
-    format("Compiled: "),
-    print_time(Time),
     print_object_file(M),
     format("Compiler options:  ~p~n", [COpts]),
     format("Exports: ~n",[]), print_exports(keysort(1, E)).
@@ -864,12 +861,6 @@ print_md5(L) ->
         _ -> ok
     end.
 
-get_compile_time(L) ->
-    case get_compile_info(L, time) of
-	{ok,Val} -> Val;
-	error -> notime
-    end.
-
 get_compile_options(L) ->
     case get_compile_info(L, options) of
 	{ok,Val} -> Val;
@@ -910,25 +901,6 @@ split_print_exports([{F1, A1}|T1], [{F2, A2} | T2]) ->
     split_print_exports(T1, T2);
 split_print_exports([], []) -> ok.
 
-print_time({Year,Month,Day,Hour,Min,_Secs}) ->
-    format("~s ~w ~w, ", [month(Month),Day,Year]),
-    format("~.2.0w:~.2.0w~n", [Hour,Min]);
-print_time(notime) ->
-    format("No compile time info available~n",[]).
-
-month(1) -> "January";
-month(2) -> "February";
-month(3) -> "March";
-month(4) -> "April";
-month(5) -> "May";
-month(6) -> "June";
-month(7) -> "July";
-month(8) -> "August";
-month(9) -> "September";
-month(10) -> "October";
-month(11) -> "November";
-month(12) -> "December".
-
 %% Just because we can't eval receive statements...
 -spec flush() -> 'ok'.
 
-- 
2.34.1

openSUSE Build Service is sponsored by