File 2221-Improved-memsup-get_system_memory_data.patch of Package erlang

From 8742e05927072aade44ae85d378e561887334362 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Thu, 15 Oct 2020 08:05:24 +0200
Subject: [PATCH] Improved memsup:get_system_memory_data()

Change the behaviour of memsup:get_system_memory_data() to the
behaviour that previously was enabled by setting the application
parameter 'memsup_improved_system_memory_data' to 'true'.
---
 lib/os_mon/doc/src/memsup.xml    | 90 +++++++-------------------------
 lib/os_mon/src/memsup.erl        | 72 ++++++++++---------------
 lib/os_mon/test/memsup_SUITE.erl | 11 ++--
 3 files changed, 51 insertions(+), 122 deletions(-)

diff --git a/lib/os_mon/doc/src/memsup.xml b/lib/os_mon/doc/src/memsup.xml
index a6f93fdba6..2e61fb9254 100644
--- a/lib/os_mon/doc/src/memsup.xml
+++ b/lib/os_mon/doc/src/memsup.xml
@@ -121,25 +121,6 @@
           systems with many concurrent processes, as each process memory
           check makes a traversal of the entire list of processes.</p>
       </item>
-      <tag><marker id="memsup_improved_system_memory_data"/><c>memsup_improved_system_memory_data = bool()</c></tag>
-      <item>
-	<p>Determines the behaviour of the
-	<seemfa marker="#get_system_memory_data/0"><c>get_system_memory_data()</c></seemfa>
-	function. When this configuration parameter is <c>false</c>,
-	<c>get_system_memory_data()</c> behaves as it has done
-	up until the point of the introduction of the configuration
-	parameter. When set to <c>true</c> new tagged tuples are
-	allowed in the result. Such new tuples may be introduced at
-	any time without prior notice. The classification of
-	<c>cached_memory</c> on Linux systems will also change so that
-	more memory is classified as <c>cached_memory</c>.
-	</p>
-	<note><p>This configuration parameter defaults <c>false</c> and will
-	do so up until OTP 23. As of OTP 24 this configuration parameter
-	will be removed and <c>get_system_memory_data()</c> will begin
-	behaving as it does now when the configuration parameter has
-	been set to <c>true</c>.</p></note>
-      </item>
     </taglist>
     <p>See <seefile marker="kernel:config">config(4)</seefile> for
       information about how to change the value of configuration
@@ -185,12 +166,24 @@
       <desc>
         <p>Invokes a memory check and returns the resulting, system
           dependent, data as a list of tagged tuples, where <c>Tag</c>
-          can be one of the following:</p>
+          currently can be one of the following:</p>
         <taglist>
           <tag><c>total_memory</c></tag>
           <item>The total amount of memory available to the Erlang emulator,
            allocated and free. May or may not be equal to the amount
-           of memory configured in the system.</item>
+          of memory configured in the system.</item>
+	  <tag><c>available_memory</c></tag>
+	  <item>Informs about the amount memory that is available for
+	  increased usage if there is an increased memory need. This
+	  value is not based on a calculation of the other provided
+	  values and should give a better value of the amount of memory
+	  that actually is available than calculating a value based on
+	  the other values reported. This value is currently only present
+	  on newer Linux kernels. If this value is not available on Linux,
+	  you can use the sum of <c>cached_memory</c>,
+	  <c>buffered_memory</c>, and <c>free_memory</c> as an
+	  approximation.
+	  </item>
           <tag><c>free_memory</c></tag>
           <item>The amount of free memory available to the Erlang emulator
            for allocation.</item>
@@ -205,6 +198,8 @@
           <tag><c>cached_memory</c></tag>
           <item>
                 The amount of memory the system uses for cached files read from disk.
+	        On Linux, also memory marked as reclaimable in the kernel slab
+		allocator will be added to this value.
           </item>
           <tag><c>total_swap</c></tag>
           <item>
@@ -218,62 +213,15 @@
 
         </taglist>
 
+	<note><p>Note that new tagged tuples may be introduced in the result
+	at any time without prior notice</p></note>
+	
 	<p>Note that the order of the tuples in the resulting list is undefined
 	and may change at any time.</p>
 	
         <p>All memory sizes are presented as number of <em>bytes</em>.</p>
         <p>Returns the empty list [] if <c>memsup</c> is not available,
           or if the memory check times out.</p>
-	<note><p>
-	  On Linux the memory available to the emulator is <c>cached_memory</c> and
-	  <c>buffered_memory</c> in addition to <c>free_memory</c>.</p>
-	</note>
-
-	<p>The above describes how it works if the configuration parameter
-	<seeerl marker="#memsup_improved_system_memory_data"><c>memsup_improved_system_memory_data</c></seeerl>
-	has been set to <c>false</c> which currently also is the default
-	behavior. If the configuration parameter is set to <c>true</c> the
-	behavior is slightly changed:</p>
-	<list>
-	  <item>
-	    <p>
-	      New tagged tuples may be added in the resulting
-	      list at any time.
-	    </p>
-	  </item>
-	  <item>
-	    <p>
-	      On Linux systems the following changes will be made:
-	    </p>
-	    <list>
-	      <item>
-		<p>
-		  A new tuple with the tag <c>available_memory</c> will be
-		  added to the result when this value is provided by the
-		  kernel. The <c>available_memory</c> value informs about
-		  the amount memory that is available for use if there is
-		  an increased memory need. This value is not based on a
-		  calculation of the other provided values and should give
-		  a better value of the amount of memory that actually is
-		  available than calculating a value based on the other
-		  values reported.
-		</p>
-	      </item>
-	      <item>
-		<p>The classification of <c>cached_memory</c> is changed.
-		Also memory marked as reclaimable in the kernel slab
-		allocator will be added to the value presented as
-		<c>cached_memory</c>.
-		</p>
-	      </item>
-	    </list>
-	  </item>
-	</list>
-	<note><p>As of OTP 24 <c>memsup_improved_system_memory_data</c>
-	configuration parameter will be	removed and
-	<c>get_system_memory_data()</c> will begin behaving as it does
-	now when the configuration parameter has been set to
-	<c>true</c>.</p></note>
       </desc>
     </func>
     <func>
diff --git a/lib/os_mon/src/memsup.erl b/lib/os_mon/src/memsup.erl
index fdd08eed63..e529334226 100644
--- a/lib/os_mon/src/memsup.erl
+++ b/lib/os_mon/src/memsup.erl
@@ -57,7 +57,6 @@
 	 ext_wd_timer,        % undefined | TimerRef
 	 pending = [],        % [reg | {reg,From} | {ext,From}]
 	 ext_pending = []     % [{ext,From}]
-%%%         ismd = false         % Improved system memory data enabled?
 	}).
 
 -define(EXT_MEM_MAP, memsup_ext_memory_type_map__).
@@ -149,7 +148,6 @@ dummy_reply(get_memory_data, true) ->
 dummy_reply(get_memory_data, false) ->
     {0,0,{self(),0}}.
 
-param_type(memsup_improved_system_memory_data, Val) when Val==true; Val==false -> true;
 param_type(memsup_system_only, Val) when Val==true; Val==false -> true;
 param_type(memory_check_interval, Val) when is_integer(Val),
                                             Val>0 -> true;
@@ -163,7 +161,6 @@ param_type(process_memory_high_watermark, Val) when is_number(Val),
 						    Val=<1 -> true;
 param_type(_Param, _Val) -> false.
 
-param_default(memsup_improved_system_memory_data) -> false;
 param_default(memsup_system_only) -> false;
 param_default(memory_check_interval) -> 1;
 param_default(memsup_helper_timeout) -> 30;
@@ -195,11 +192,9 @@ init([]) ->
 		       exit({unsupported_os, OS})
 	       end,
 
-    ISMD = os_mon:get_env(memsup, memsup_improved_system_memory_data),
-
     Pid = if
 	      PortMode ->
-		  spawn_link(fun() -> port_init(ISMD) end);
+		  spawn_link(fun() -> port_init() end);
 	      not PortMode ->
 		  undefined
 	  end,
@@ -236,7 +231,6 @@ init([]) ->
 		helper_timeout     = sec_to_ms(HelperTimeout),
 		sys_mem_watermark  = SysMem,
 		proc_mem_watermark = ProcMem,
-%%%                ismd               = ISMD,
 
 		pid=Pid}}.
 
@@ -648,10 +642,10 @@ get_ext_memory_usage(OS, {Alloc, Total}) ->
 
 %%--Collect memory data, using port-------------------------------------
 
-port_init(ISMD) ->
+port_init() ->
     process_flag(trap_exit, true),
     Port = start_portprogram(),
-    port_idle(Port, ISMD).
+    port_idle(Port).
 
 start_portprogram() ->
     os_mon:open_port("memsup",[{packet,1}]).
@@ -664,20 +658,20 @@ start_portprogram() ->
 %%      should still wait for port response (which should come
 %%      eventually!) but not receive any requests or cancellations
 %%      meanwhile to prevent getting out of synch.
-port_idle(Port, ISMD) ->
+port_idle(Port) ->
     receive
 	{Memsup, collect_sys} ->
 	    Port ! {self(), {command, [?SHOW_MEM]}},
-	    get_memory_usage(Port, undefined, Memsup, ISMD);
+	    get_memory_usage(Port, undefined, Memsup);
 	{Memsup, collect_ext_sys} ->
 	    Port ! {self(), {command, [?SHOW_SYSTEM_MEM]}},
-	    get_ext_memory_usage(Port, #{}, Memsup, ISMD);
+	    get_ext_memory_usage(Port, #{}, Memsup);
 	cancel ->
 	    %% Received after reply already has been delivered...
-	    port_idle(Port, ISMD);
+	    port_idle(Port);
 	ext_cancel ->
 	    %% Received after reply already has been delivered...
-	    port_idle(Port, ISMD);
+	    port_idle(Port);
 	close ->
 	    port_close(Port);
 	{Port, {data, Data}} ->
@@ -688,16 +682,16 @@ port_idle(Port, ISMD) ->
 	    port_close(Port)
     end.
 
-get_memory_usage(Port, Alloc, Memsup, ISMD) ->
+get_memory_usage(Port, Alloc, Memsup) ->
     receive
 	{Port, {data, Data}} when Alloc==undefined ->
-	    get_memory_usage(Port, erlang:list_to_integer(Data, 16), Memsup, ISMD);
+	    get_memory_usage(Port, erlang:list_to_integer(Data, 16), Memsup);
 	{Port, {data, Data}} ->
 	    Total = erlang:list_to_integer(Data, 16),
 	    Memsup ! {collected_sys, {Alloc, Total}},
-	    port_idle(Port, ISMD);
+	    port_idle(Port);
 	cancel ->
-	    get_memory_usage_cancelled(Port, Alloc, ISMD);
+	    get_memory_usage_cancelled(Port, Alloc);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
@@ -705,12 +699,12 @@ get_memory_usage(Port, Alloc, Memsup, ISMD) ->
 	{'EXIT', _Memsup, _Reason} ->
 	    port_close(Port)
     end.
-get_memory_usage_cancelled(Port, Alloc, ISMD) ->
+get_memory_usage_cancelled(Port, Alloc) ->
     receive
 	{Port, {data, _Data}} when Alloc==undefined ->
-	    get_memory_usage_cancelled(Port, 0, ISMD);
+	    get_memory_usage_cancelled(Port, 0);
 	{Port, {data, _Data}} ->
-	    port_idle(Port, ISMD);
+	    port_idle(Port);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
@@ -728,24 +722,16 @@ tag2atag(Port, Tag) ->
             exit({memsup_port_error, {Port,[Tag]}})
     end.
 
-get_ext_memory_usage(Port, Accum, Memsup, ISMD) ->
+get_ext_memory_usage(Port, Accum, Memsup) ->
     receive
 	{Port, {data, [?SHOW_SYSTEM_MEM_END]}} ->
 	    Memsup ! {collected_ext_sys, maps:to_list(Accum)},
-	    port_idle(Port, ISMD);
-	{Port, {data, [?MEM_CACHED_X]}} when ISMD == false ->
-            %% Improved system memory data not enabled; drop value...
-            get_ext_memory_usage(tag2atag(Port, ?MEM_CACHED_X), Port,
-                                 Accum, Memsup, ISMD, true);
-	{Port, {data, [?MEM_AVAIL]}} when ISMD == false ->
-            %% Improved system memory data not enabled; drop value...
-            get_ext_memory_usage(tag2atag(Port, ?MEM_AVAIL), Port,
-                                 Accum, Memsup, ISMD, true);
+	    port_idle(Port);
 	{Port, {data, [Tag]}} ->
             get_ext_memory_usage(tag2atag(Port, Tag), Port, Accum,
-                                 Memsup, ISMD, false);
+                                 Memsup);
 	ext_cancel ->
-	    get_ext_memory_usage_cancelled(Port, ISMD);
+	    get_ext_memory_usage_cancelled(Port);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
@@ -753,13 +739,13 @@ get_ext_memory_usage(Port, Accum, Memsup, ISMD) ->
 	{'EXIT', _Memsup, _Reason} ->
 	    port_close(Port)
     end.
-get_ext_memory_usage_cancelled(Port, ISMD) ->
+get_ext_memory_usage_cancelled(Port) ->
     receive
 	{Port, {data, [?SHOW_SYSTEM_MEM_END]}} ->
-	    port_idle(Port, ISMD);
+	    port_idle(Port);
 	{Port, {data, [Tag]}} ->
             get_ext_memory_usage_cancelled(tag2atag(Port, Tag),
-                                           Port, ISMD);
+                                           Port);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
@@ -768,11 +754,9 @@ get_ext_memory_usage_cancelled(Port, ISMD) ->
 	    port_close(Port)
     end.
 
-get_ext_memory_usage(ATag, Port, Accum0, Memsup, ISMD, Drop) ->
+get_ext_memory_usage(ATag, Port, Accum0, Memsup) ->
     receive
-	{Port, {data, _Data}} when Drop == true ->
-	    get_ext_memory_usage(Port, Accum0, Memsup, ISMD);
-	{Port, {data, Data}} when Drop == false ->
+	{Port, {data, Data}} ->
             Value = erlang:list_to_integer(Data, 16),
             Accum = case maps:get(ATag, Accum0, undefined) of
                         undefined ->
@@ -780,9 +764,9 @@ get_ext_memory_usage(ATag, Port, Accum0, Memsup, ISMD, Drop) ->
                         PrevValue ->
                             maps:put(ATag, Value + PrevValue, Accum0)
                     end,
-	    get_ext_memory_usage(Port, Accum, Memsup, ISMD);
+	    get_ext_memory_usage(Port, Accum, Memsup);
 	cancel ->
-	    get_ext_memory_usage_cancelled(ATag, Port, ISMD);
+	    get_ext_memory_usage_cancelled(ATag, Port);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
@@ -790,10 +774,10 @@ get_ext_memory_usage(ATag, Port, Accum0, Memsup, ISMD, Drop) ->
 	{'EXIT', _Memsup, _Reason} ->
 	    port_close(Port)
     end.
-get_ext_memory_usage_cancelled(_ATag, Port, ISMD) ->
+get_ext_memory_usage_cancelled(_ATag, Port) ->
     receive
 	{Port, {data, _Data}} ->
-	    get_ext_memory_usage_cancelled(Port, ISMD);
+	    get_ext_memory_usage_cancelled(Port);
 	close ->
 	    port_close(Port);
 	{'EXIT', Port, Reason} ->
diff --git a/lib/os_mon/test/memsup_SUITE.erl b/lib/os_mon/test/memsup_SUITE.erl
index 97f97e21cc..1892c49583 100644
--- a/lib/os_mon/test/memsup_SUITE.erl
+++ b/lib/os_mon/test/memsup_SUITE.erl
@@ -32,7 +32,8 @@
 
 
 -define(SYSTEM_MEMORY_DATA_TAGS,
-        [total_memory,
+        [available_memory,
+         total_memory,
          free_memory,
          system_total_memory,
          largest_free,
@@ -43,10 +44,6 @@
          buffered_memory,
          shared_memory]).
 
--define(IMPROVED_SYSTEM_MEMORY_DATA_TAGS,
-        [available_memory | ?SYSTEM_MEMORY_DATA_TAGS]).
-
-
 init_per_suite(Config) when is_list(Config) ->
     ok = application:start(os_mon),
     Config.
@@ -726,7 +723,7 @@ otp_5910(Config) when is_list(Config) ->
     ok.
 
 improved_system_memory_data(Config) ->
-    {ok, Node} = start_node(Config, "-os_mon memsup_improved_system_memory_data true"),
+    {ok, Node} = start_node(Config),
     ok = rpc:call(Node, application, start, [sasl]),
     ok = rpc:call(Node, application, start, [os_mon]),
 
@@ -734,7 +731,7 @@ improved_system_memory_data(Config) ->
 
     stop_node(Node),
 
-    Tags = ?IMPROVED_SYSTEM_MEMORY_DATA_TAGS,
+    Tags = ?SYSTEM_MEMORY_DATA_TAGS,
     AvailableMemoryPresent
         = lists:foldl(fun ({Tag,Value}, AMP) when is_atom(Tag),
                                                   is_integer(Value),
-- 
2.26.2

openSUSE Build Service is sponsored by