File 0501-os_mon-Remove-unused-code_change-3-functions.patch of Package erlang

From 82f43566ca3e35e724abe1bbb1be221f57afed65 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 27 Aug 2020 06:09:49 +0200
Subject: [PATCH 1/2] os_mon: Remove unused code_change/3 functions

The `os_mon.appup` file specifies that the `os_mon` application
should be restarted when upgrading or downgrading. Therefore, there
is no need for any `code_change/3` function.
---
 lib/os_mon/src/cpu_sup.erl        |  19 +---
 lib/os_mon/src/disksup.erl        |  26 +-----
 lib/os_mon/src/memsup.erl         | 148 +-----------------------------
 lib/os_mon/src/nteventlog.erl     |  27 +-----
 lib/os_mon/src/os_mon_sysinfo.erl |  19 +---
 lib/os_mon/src/os_sup.erl         |  65 +------------
 6 files changed, 6 insertions(+), 298 deletions(-)

diff --git a/lib/os_mon/src/cpu_sup.erl b/lib/os_mon/src/cpu_sup.erl
index d28f229b3e..8c130e28ee 100644
--- a/lib/os_mon/src/cpu_sup.erl
+++ b/lib/os_mon/src/cpu_sup.erl
@@ -29,7 +29,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 %% Internal protocol with the port program
 -define(nprocs,"n").
@@ -199,23 +199,6 @@ handle_info(_Info, State) ->
 terminate(_Reason, State) ->
     exit(State#state.server, normal).
 
-%% os_mon-2.0
-%% For live downgrade to/upgrade from os_mon-1.8[.1]
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-	    process_flag(trap_exit, false);
-
-	%% Upgrade to this version
-	_Vsn ->
-	    process_flag(trap_exit, true)
-    end,
-    {ok, PrevState};
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% internal functions 
 %%----------------------------------------------------------------------
diff --git a/lib/os_mon/src/disksup.erl b/lib/os_mon/src/disksup.erl
index 4253067c90..dcc624212c 100644
--- a/lib/os_mon/src/disksup.erl
+++ b/lib/os_mon/src/disksup.erl
@@ -29,7 +29,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 %% Other exports
 -export([format_status/2, parse_df/2]).
@@ -170,30 +170,6 @@ terminate(_Reason, State) ->
     end,
     ok.
 
-%% os_mon-2.0.1
-%% For live downgrade to/upgrade from os_mon-1.8[.1]
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-	    State = case PrevState#state.port of
-			not_used -> PrevState#state{port=noport};
-			_ -> PrevState
-		    end,
-	    {ok, State};
-
-	%% Upgrade to this version
-	_Vsn ->
-	    State = case PrevState#state.port of
-			noport -> PrevState#state{port=not_used};
-			_ -> PrevState
-		    end,
-	    {ok, State}
-    end;
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% Other exports
 %%----------------------------------------------------------------------
diff --git a/lib/os_mon/src/memsup.erl b/lib/os_mon/src/memsup.erl
index bbf120e973..293e893d12 100644
--- a/lib/os_mon/src/memsup.erl
+++ b/lib/os_mon/src/memsup.erl
@@ -32,7 +32,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 %% Other exports
 -export([format_status/2]).
@@ -534,152 +534,6 @@ terminate(_Reason, State) ->
     clear_alarms(),
     ok.
 
-%% os_mon-2.0.1
-%% For live downgrade to/upgrade from os_mon-1.8[.1] and -2.0
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-
-	    %% Kill the helper process, if there is one,
-	    %% and flush messages from it
-	    case PrevState#state.pid of
-		Pid when is_pid(Pid) ->
-		    unlink(Pid), % to prevent 'EXIT' message
-		    exit(Pid, cancel);
-		undefined -> ignore
-	    end,
-	    flush(collected_sys),
-	    flush(collected_ext_sys),
-
-	    %% Cancel timers, flush timeout messages
-	    %% and send dummy replies to any pending clients
-	    case PrevState#state.wd_timer of
-		undefined ->
-		    ignore;
-		TimerRef1 ->
-                    ok = erlang:cancel_timer(TimerRef1, [{async,true}]),
-		    SysOnly = PrevState#state.sys_only,
-		    MemUsage = dummy_reply(get_memory_data, SysOnly),
-		    SysMemUsage1 = dummy_reply(get_system_memory_data),
-		    reply(PrevState#state.pending,MemUsage,SysMemUsage1)
-	    end,
-	    case PrevState#state.ext_wd_timer of
-		undefined ->
-		    ignore;
-		TimerRef2 ->
-                    ok = erlang:cancel_timer(TimerRef2, [{async,true}]),
-		    SysMemUsage2 = dummy_reply(get_system_memory_data),
-		    reply(PrevState#state.pending, undef, SysMemUsage2)
-	    end,
-	    flush(reg_collection_timeout),
-	    flush(ext_collection_timeout),
-
-	    %% Downgrade to old state record
-	    State = {state,
-		     PrevState#state.timeout,
-		     PrevState#state.mem_usage,
-		     PrevState#state.worst_mem_user,
-		     PrevState#state.sys_mem_watermark,
-		     PrevState#state.proc_mem_watermark,
-		     not PrevState#state.sys_only, % collect_procmem
-		     undefined, % wd_timer
-		     [],        % pending
-		     undefined, % ext_wd_timer
-		     [],        % ext_pending
-		     PrevState#state.helper_timeout},
-	    {ok, State};
-
-	%% Upgrade to this version
-	_Vsn ->
-
-	    %% Old state record
-	    {state,
-	     Timeout, MemUsage, WorstMemUser,
-	     SysMemWatermark, ProcMemWatermark, CollProc,
-	     WDTimer, Pending, ExtWDTimer, ExtPending,
-	     HelperTimeout} = PrevState,
-	    SysOnly = not CollProc,
-
-	    %% Flush memsup_helper messages
-	    flush(collected_sys),
-	    flush(collected_proc),
-	    flush(collected_ext_sys),
-		     
-	    %% Cancel timers, flush timeout messages
-	    %% and send dummy replies to any pending clients
-	    case WDTimer of
-		undefined ->
-		    ignore;
-		TimerRef1 ->
-                    ok = erlang:cancel_timer(TimerRef1, [{async,true}]),
-		    MemUsage = dummy_reply(get_memory_data, SysOnly),
-		    Pending2 = lists:map(fun(From) -> {reg,From} end,
-					 Pending),
-		    reply(Pending2, MemUsage, undef)
-	    end,
-	    case ExtWDTimer of
-		undefined ->
-		    ignore;
-		TimerRef2 ->
-                    ok = erlang:cancel_timer(TimerRef2, [{async,true}]),
-		    SysMemUsage = dummy_reply(get_system_memory_data),
-		    ExtPending2 = lists:map(fun(From) -> {ext,From} end,
-					    ExtPending),
-		    reply(ExtPending2, undef, SysMemUsage)
-	    end,
-	    flush(reg_collection_timeout),
-	    flush(ext_collection_timeout),
-
-	    OS = os:type(),
-	    PortMode = case OS of
-			   {unix, darwin} -> false;
-			   {unix, freebsd} -> false;
-			   {unix, dragonfly} -> false;
-			   {unix, linux} -> false;
-			   {unix, openbsd} -> true;
-			   {unix, netbsd} -> true;
-			   {unix, sunos} -> true;
-			   {win32, _OSname} -> false
-		       end,
-	    Pid = if
-		      PortMode -> spawn_link(fun() -> port_init(false) end);
-		      not PortMode -> undefined
-		  end,
-
-	    %% Upgrade to this state record
-	    State = #state{os = OS,
-			   port_mode = PortMode,
-			   mem_usage = MemUsage,
-			   worst_mem_user = WorstMemUser,
-			   sys_only  = SysOnly,
-			   timeout         = Timeout,
-			   helper_timeout  = HelperTimeout,
-			   sys_mem_watermark = SysMemWatermark,
-			   proc_mem_watermark = ProcMemWatermark,
-			   pid                = Pid,
-			   wd_timer           = undefined,
-			   ext_wd_timer       = undefined,
-			   pending            = [],
-			   ext_pending        = []},
-	    {ok, State}
-    end;
-code_change(_Vsn, State, "2.0") ->
-
-    %% Restart the port process (it must use new memsup code)
-    Pid = case State#state.port_mode of
-	      true ->
-		  State#state.pid ! close,
-		  spawn_link(fun() -> port_init(false) end);
-	      false ->
-		  State#state.pid
-	  end,
-    {ok, State#state{pid=Pid}};
-	  
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% Other exports
 %%----------------------------------------------------------------------
diff --git a/lib/os_mon/src/nteventlog.erl b/lib/os_mon/src/nteventlog.erl
index 4b02d3ff7e..5e88a73510 100644
--- a/lib/os_mon/src/nteventlog.erl
+++ b/lib/os_mon/src/nteventlog.erl
@@ -25,7 +25,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 -record(state, {port, mfa}).
 
@@ -92,31 +92,6 @@ terminate(_Reason, State) ->
     end,
     ok.
 
-%% os_mon-2.0
-%% For live downgrade to/upgrade from os_mon-1.8[.1]
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-	    process_flag(trap_exit, false),
-
-	    %% Downgrade to old State tuple
-	    State = {PrevState#state.port, PrevState#state.mfa},
-	    {ok, State};
-
-	%% Upgrade to this version
-	_Vsn ->
-	    process_flag(trap_exit, true),
-
-	    %% Upgrade to this state record
-	    {Port, MFA} = PrevState,
-	    State = #state{port=Port, mfa=MFA},
-	    {ok, State}
-    end;
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% Internal functions
 %%----------------------------------------------------------------------
diff --git a/lib/os_mon/src/os_mon_sysinfo.erl b/lib/os_mon/src/os_mon_sysinfo.erl
index e87e597420..0694dab7e1 100644
--- a/lib/os_mon/src/os_mon_sysinfo.erl
+++ b/lib/os_mon/src/os_mon_sysinfo.erl
@@ -26,7 +26,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 -define(DISK_INFO, $d).
 -define(MEM_INFO,  $m).
@@ -87,23 +87,6 @@ terminate(_Reason, State) ->
     end,
     ok.
 
-%% os_mon-2.0
-%% For live downgrade to/upgrade from os_mon-1.8[.1]
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-	    process_flag(trap_exit, false);
-
-	%% Upgrade to this version
-	_Vsn ->
-	    process_flag(trap_exit, true)
-    end,
-    {ok, PrevState};
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% Internal functions
 %%----------------------------------------------------------------------
diff --git a/lib/os_mon/src/os_sup.erl b/lib/os_mon/src/os_sup.erl
index 71c9137588..77cd407a82 100644
--- a/lib/os_mon/src/os_sup.erl
+++ b/lib/os_mon/src/os_sup.erl
@@ -28,7 +28,7 @@
 
 %% gen_server callbacks
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
-	 terminate/2, code_change/3]).
+	 terminate/2]).
 
 -record(state, {port, mfa, config, path, conf}).
 
@@ -159,69 +159,6 @@ terminate(_Reason, #state{port=Port} = State) ->
 	    ok
     end.
 
-%% os_mon-2.0
-%% For live downgrade to/upgrade from os_mon-1.8[.1]
-code_change(Vsn, PrevState, "1.8") ->
-    case Vsn of
-
-	%% Downgrade from this version
-	{down, _Vsn} ->
-
-	    %% Find out the error tag used
-	    {DefM, DefF, _} = param_default(os_sup_mfa),
-	    Tag = case PrevState#state.mfa of
-
-		      %% Default callback function is used, then use
-		      %% the corresponding tag
-		      {DefM, DefF, [Tag0]} ->
-			  Tag0;
-
-		      %% Default callback function is *not* used
-		      %% (before the downgrade, that is)
-		      %% -- check the configuration parameter
-		      _ ->
-			  case application:get_env(os_mon,
-						   os_sup_errortag) of
-			      {ok, Tag1} ->
-				  Tag1;
-
-			      %% (actually, if it has no value,
-			      %%  the process should terminate
-			      %%  according to 1.8.1 version, but that
-			      %%  seems too harsh here)
-			      _ ->
-				  std_error
-			  end
-		  end,
-		      
-	    %% Downgrade to old state record
-	    State = {state, PrevState#state.port, Tag},
-	    {ok, State};
-
-	%% Upgrade to this version
-	_Vsn ->
-
-	    {state, Port, Tag} = PrevState,
-
-	    {DefM, DefF, _} = param_default(os_sup_mfa),
-	    MFA  = {DefM, DefF, [Tag]},
-
-	    %% We can safely assume the following configuration
-	    %% parameters are defined, otherwise os_sup would never had
-	    %% started in the first place.
-	    %% (We can *not* safely assume they haven't been changed,
-	    %%  but that's a weakness inherited from the 1.8.1 version)
-	    Path = application:get_env(os_mon, os_sup_own),
-	    Conf = application:get_env(os_mon, os_sup_syslogconf),
-
-	    %% Upgrade to this state record
-	    State = #state{port=Port, mfa=MFA, config=true,
-			   path=Path, conf=Conf},
-	    {ok, State}
-    end;
-code_change(_OldVsn, State, _Extra) ->
-    {ok, State}.
-
 %%----------------------------------------------------------------------
 %% Internal functions
 %%----------------------------------------------------------------------
-- 
2.26.2

openSUSE Build Service is sponsored by