File 0523-kernel-erts-Use-memavailable-for-tests-when-availabl.patch of Package erlang

From 32a34256200d7f7bc598a62ec1333c823f35e47d Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Wed, 19 Oct 2022 12:21:40 +0200
Subject: [PATCH 6/9] kernel|erts: Use memavailable for tests when available

---
 erts/emulator/test/alloc_SUITE.erl        | 16 ++++++----------
 erts/emulator/test/binary_SUITE.erl       | 23 ++++++++++-------------
 erts/emulator/test/bs_construct_SUITE.erl |  9 +++++++--
 erts/emulator/test/distribution_SUITE.erl |  6 ++++--
 erts/emulator/test/hash_SUITE.erl         | 23 +++++++++++------------
 erts/emulator/test/map_SUITE.erl          | 17 ++++++++---------
 erts/emulator/test/process_SUITE.erl      | 19 +++++++++----------
 erts/emulator/test/tuple_SUITE.erl        | 19 +++++++++----------
 lib/kernel/test/application_SUITE.erl     | 21 ++++++++++++++++++---
 lib/kernel/test/file_SUITE.erl            |  9 +++++++--
 10 files changed, 89 insertions(+), 73 deletions(-)

diff --git a/erts/emulator/test/alloc_SUITE.erl b/erts/emulator/test/alloc_SUITE.erl
index 3f128717b2..cea3d610a0 100644
--- a/erts/emulator/test/alloc_SUITE.erl
+++ b/erts/emulator/test/alloc_SUITE.erl
@@ -485,16 +485,12 @@ free_memory() ->
     %% Free memory in MB.
     try
 	SMD = memsup:get_system_memory_data(),
-	{value, {free_memory, Free}} = lists:keysearch(free_memory, 1, SMD),
-	TotFree = (Free +
-		   case lists:keysearch(cached_memory, 1, SMD) of
-		       {value, {cached_memory, Cached}} -> Cached;
-		       false -> 0
-		   end +
-		   case lists:keysearch(buffered_memory, 1, SMD) of
-		       {value, {buffered_memory, Buffed}} -> Buffed;
-		       false -> 0
-		   end),
+        TotFree = proplists:get_value(
+                    available_memory, SMD,
+                    proplists:get_value(free_memory, SMD) +
+                        proplists:get_value(cached_memory, SMD, 0) +
+                        proplists:get_value(buffered_memory, SMD, 0)
+                   ),
 	TotFree div (1024*1024)
     catch
 	error : undef ->
diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl
index c5c64c8289..5a72350d9d 100644
--- a/erts/emulator/test/binary_SUITE.erl
+++ b/erts/emulator/test/binary_SUITE.erl
@@ -471,10 +471,8 @@ bad_term_to_binary(Config) when is_list(Config) ->
 t2b_system_limit(Config) when is_list(Config) ->
     case erlang:system_info(wordsize) of
         8 ->
-            case proplists:get_value(system_total_memory,
-                                     memsup:get_system_memory_data()) of
-                Memory when is_integer(Memory),
-                            Memory > 6*1024*1024*1024 ->
+            case total_memory() of
+                Memory when is_integer(Memory), Memory > 6 ->
                     do_t2b_system_limit();
                 _ ->
                     {skipped, "Not enough memory on this machine"}
@@ -1039,15 +1037,14 @@ report_throughput(Fun, NrOfItems) ->
 total_memory() ->
     %% Total memory in GB.
     try
-	MemoryData = memsup:get_system_memory_data(),
-	case lists:keysearch(total_memory, 1, MemoryData) of
-	    {value, {total_memory, TM}} ->
-		TM div (1024*1024*1024);
-	    false ->
-		{value, {system_total_memory, STM}} =
-		    lists:keysearch(system_total_memory, 1, MemoryData),
-		STM div (1024*1024*1024)
-	end
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024*1024)
     catch
 	_ : _ ->
 	    undefined
diff --git a/erts/emulator/test/bs_construct_SUITE.erl b/erts/emulator/test/bs_construct_SUITE.erl
index 0d083bb8d7..7bc8c0b565 100644
--- a/erts/emulator/test/bs_construct_SUITE.erl
+++ b/erts/emulator/test/bs_construct_SUITE.erl
@@ -955,8 +955,13 @@ id(I) -> I.
 
 memsize() ->
     application:ensure_all_started(os_mon),
-    {Tot,_Used,_}  = memsup:get_memory_data(),
-    Tot.
+    case proplists:get_value(available_memory, memsup:get_system_memory_data()) of
+        undefined ->
+            {Tot,_Used,_}  = memsup:get_memory_data(),
+            Tot;
+        Available ->
+            Available
+    end.
 
 -define(FP16(EncodedInt, Float),
         (fun(NlInt, NlFloat) ->
diff --git a/erts/emulator/test/distribution_SUITE.erl b/erts/emulator/test/distribution_SUITE.erl
index ba422fd9df..edab0be20b 100644
--- a/erts/emulator/test/distribution_SUITE.erl
+++ b/erts/emulator/test/distribution_SUITE.erl
@@ -1773,8 +1773,10 @@ flush() ->
 system_limit(Config) when is_list(Config) ->
     case erlang:system_info(wordsize) of
         8 ->
-            case proplists:get_value(system_total_memory,
-                                     memsup:get_system_memory_data()) of
+            SMD = memsup:get_system_memory_data(),
+            case proplists:get_value(
+                   available_memory, SMD,
+                   proplists:get_value(system_total_memory, SMD)) of
                 Memory when is_integer(Memory),
                             Memory > 6*1024*1024*1024 ->
                     test_system_limit(Config),
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index c8034c3835..3232607c9d 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -704,21 +704,20 @@ run_when_enough_resources(Fun) ->
                            [Mem, Bits, Build])}
     end.
 
-%% Total memory in GB
 total_memory() ->
+    %% Total memory in GB.
     try
-        MemoryData = memsup:get_system_memory_data(),
-        case lists:keysearch(total_memory, 1, MemoryData) of
-            {value, {total_memory, TM}} ->
-        	TM div (1024*1024*1024);
-            false ->
-        	{value, {system_total_memory, STM}} =
-        	    lists:keysearch(system_total_memory, 1, MemoryData),
-        	STM div (1024*1024*1024)
-        end
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024*1024)
     catch
-        _ : _ ->
-            undefined
+	_ : _ ->
+	    undefined
     end.
 
 start_node(X) ->
diff --git a/erts/emulator/test/map_SUITE.erl b/erts/emulator/test/map_SUITE.erl
index 72f1c1174c..23c072ce86 100644
--- a/erts/emulator/test/map_SUITE.erl
+++ b/erts/emulator/test/map_SUITE.erl
@@ -3526,15 +3526,14 @@ run_when_enough_resources(Fun) ->
 total_memory() ->
     %% Total memory in GB.
     try
-	MemoryData = memsup:get_system_memory_data(),
-	case lists:keysearch(total_memory, 1, MemoryData) of
-	    {value, {total_memory, TM}} ->
-		TM div (1024*1024*1024);
-	    false ->
-		{value, {system_total_memory, STM}} =
-		    lists:keysearch(system_total_memory, 1, MemoryData),
-		STM div (1024*1024*1024)
-	end
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024*1024)
     catch
 	_ : _ ->
 	    undefined
diff --git a/erts/emulator/test/process_SUITE.erl b/erts/emulator/test/process_SUITE.erl
index ee9834b44f..96528dbc00 100644
--- a/erts/emulator/test/process_SUITE.erl
+++ b/erts/emulator/test/process_SUITE.erl
@@ -4914,17 +4914,16 @@ sys_mem_cond_run(OrigReqSizeMB, TestFun) when is_integer(OrigReqSizeMB) ->
 
 
 total_memory() ->
-    %% Totat memory in MB.
+    %% Total memory in MB.
     try
-	MemoryData = memsup:get_system_memory_data(),
-	case lists:keysearch(total_memory, 1, MemoryData) of
-	    {value, {total_memory, TM}} ->
-		TM div (1024*1024);
-	    false ->
-		{value, {system_total_memory, STM}} =
-		    lists:keysearch(system_total_memory, 1, MemoryData),
-		STM div (1024*1024)
-	end
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024)
     catch
 	_ : _ ->
 	    undefined
diff --git a/erts/emulator/test/tuple_SUITE.erl b/erts/emulator/test/tuple_SUITE.erl
index 94fe6c2a0a..0e47c3a1a5 100644
--- a/erts/emulator/test/tuple_SUITE.erl
+++ b/erts/emulator/test/tuple_SUITE.erl
@@ -623,17 +623,16 @@ sys_mem_cond_run(ReqSizeMB, TestFun) when is_integer(ReqSizeMB) ->
 
 
 total_memory() ->
-    %% Totat memory in MB.
+    %% Total memory in MB.
     try
-	MemoryData = memsup:get_system_memory_data(),
-	case lists:keysearch(total_memory, 1, MemoryData) of
-	    {value, {total_memory, TM}} ->
-		TM div (1024*1024);
-	    false ->
-		{value, {system_total_memory, STM}} =
-		    lists:keysearch(system_total_memory, 1, MemoryData),
-		STM div (1024*1024)
-	end
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024)
     catch
 	_ : _ ->
 	    undefined
diff --git a/lib/kernel/test/application_SUITE.erl b/lib/kernel/test/application_SUITE.erl
index 6817435576..0668c28692 100644
--- a/lib/kernel/test/application_SUITE.erl
+++ b/lib/kernel/test/application_SUITE.erl
@@ -2188,10 +2188,9 @@ do_configfd_test_bash() ->
                        "3> /dev/null ")),
     %% Check that file descriptor with a huge amount of data fails
     case application:start(os_mon) of
-        ok -> case proplists:get_value(system_total_memory,
-                                       memsup:get_system_memory_data()) of
+        ok -> case total_memory() of
                   Memory when is_integer(Memory),
-                              Memory > 16*1024*1024*1024 ->
+                              Memory > 16 ->
                       application:stop(os_mon),
                       true =
                           ("magic42" =/=
@@ -2210,6 +2209,22 @@ do_configfd_test_bash() ->
     end,
     ok.
 
+total_memory() ->
+    %% Total memory in GB.
+    try
+	SMD = memsup:get_system_memory_data(),
+        TM = proplists:get_value(
+               available_memory, SMD,
+               proplists:get_value(
+                 total_memory, SMD,
+                 proplists:get_value(
+                   system_total_memory, SMD))),
+        TM div (1024*1024*1024)
+    catch
+	_ : _ ->
+	    undefined
+    end.
+
 %% Test that one can get configuration from file descriptor with the
 %% -configfd option
 configfd_bash(Conf) when is_list(Conf) ->
diff --git a/lib/kernel/test/file_SUITE.erl b/lib/kernel/test/file_SUITE.erl
index 3759ef1c22..b791a577f0 100644
--- a/lib/kernel/test/file_SUITE.erl
+++ b/lib/kernel/test/file_SUITE.erl
@@ -4888,5 +4888,10 @@ disc_free(Path) ->
     end.
 
 memsize() ->
-    {Tot,_Used,_}  = memsup:get_memory_data(),
-    Tot.
+    case proplists:get_value(available_memory, memsup:get_system_memory_data()) of
+        undefined ->
+            {Tot,_Used,_}  = memsup:get_memory_data(),
+            Tot;
+        Available ->
+            Available
+    end.
-- 
2.35.3

openSUSE Build Service is sponsored by