File 0458-kernel-Adjust-disk_log-tests.patch of Package erlang

From 7713d6e37f5fb3b105834ab96121d728d4bb5065 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Mon, 2 Jul 2018 10:28:02 +0200
Subject: [PATCH 2/2] kernel: Adjust disk_log tests

---
 lib/kernel/test/disk_log_SUITE.erl | 99 ++++++++++++++++++++++++++++----------
 1 file changed, 74 insertions(+), 25 deletions(-)

diff --git a/lib/kernel/test/disk_log_SUITE.erl b/lib/kernel/test/disk_log_SUITE.erl
index 0709a6e766..9704c3b28c 100644
--- a/lib/kernel/test/disk_log_SUITE.erl
+++ b/lib/kernel/test/disk_log_SUITE.erl
@@ -1750,7 +1750,7 @@ block_queue(Conf) when is_list(Conf) ->
     true = [{1,a},{2,b},{3,c},{4,d},{5,e},{6,f},{7,g},{8,h}] == Terms,
     del(File, 2),
     Q = qlen(),
-    true = (P0 == pps()),
+    check_pps(P0),
     ok.
 
 %% OTP-4880. Blocked processes did not get disk_log_stopped message.
@@ -1782,7 +1782,7 @@ block_queue2(Conf) when is_list(Conf) ->
     {ok,<<>>} = file:read_file(File ++ ".1"),
     del(File, No),
     Q = qlen(),
-    true = (P0 == pps()),
+    check_pps(P0),
     ok.
 
 
@@ -2119,7 +2119,7 @@ close_block(Conf) when is_list(Conf) ->
     0 = sync_do(Pid2, users),
     sync_do(Pid2, terminate),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Users terminate (no link...).
     Pid3 = spawn_link(?MODULE, lserv, [n]),
@@ -2137,7 +2137,7 @@ close_block(Conf) when is_list(Conf) ->
     disk_log:close(n),
     disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking owner terminates.
     Pid5 = spawn_link(?MODULE, lserv, [n]),
@@ -2154,7 +2154,7 @@ close_block(Conf) when is_list(Conf) ->
     1 = users(n),
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking user terminates.
     Pid6 = spawn_link(?MODULE, lserv, [n]),
@@ -2174,7 +2174,7 @@ close_block(Conf) when is_list(Conf) ->
     1 = users(n),
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking owner terminates.
     Pid7 = spawn_link(?MODULE, lserv, [n]),
@@ -2192,7 +2192,7 @@ close_block(Conf) when is_list(Conf) ->
     1 = users(n),
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Two owners, the blocking one terminates.
     Pid8 = spawn_link(?MODULE, lserv, [n]),
@@ -2207,7 +2207,7 @@ close_block(Conf) when is_list(Conf) ->
     0 = sync_do(Pid9, users),
     sync_do(Pid9, terminate),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking user closes.
     Pid10 = spawn_link(?MODULE, lserv, [n]),
@@ -2225,7 +2225,7 @@ close_block(Conf) when is_list(Conf) ->
     ok = disk_log:close(n),
     sync_do(Pid10, terminate),
     {error, no_such_log} = disk_log:info(n),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking user unblocks and closes.
     Pid11 = spawn_link(?MODULE, lserv, [n]),
@@ -2244,7 +2244,7 @@ close_block(Conf) when is_list(Conf) ->
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
     sync_do(Pid11, terminate),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking owner closes.
     Pid12 = spawn_link(?MODULE, lserv, [n]),
@@ -2263,7 +2263,7 @@ close_block(Conf) when is_list(Conf) ->
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
     sync_do(Pid12, terminate),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% Blocking owner unblocks and closes.
     Pid13 = spawn_link(?MODULE, lserv, [n]),
@@ -2283,7 +2283,7 @@ close_block(Conf) when is_list(Conf) ->
     ok = disk_log:close(n),
     {error, no_such_log} = disk_log:info(n),
     sync_do(Pid13, terminate),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     del(File, No),	% cleanup
     ok.
@@ -2487,7 +2487,7 @@ error_repair(Conf) when is_list(Conf) ->
     P0 = pps(),
     {error, {file_error, _, _}} =
 	disk_log:open([{name, n}, {file, File}, {type, wrap}, {size,{40,4}}]),
-    true = (P0 == pps()),
+    check_pps(P0),
     del(File, No),
     ok = file:del_dir(Dir),
 
@@ -2506,7 +2506,7 @@ error_repair(Conf) when is_list(Conf) ->
 	disk_log:open([{name, n}, {file, File}, {type, wrap},
 		       {format, internal}, {size, {40,No}}]),
     ok = disk_log:close(n),
-    true = (P1 == pps()),
+    check_pps(P1),
     del(File, No),
     receive {info_msg, _, "disk_log: repairing" ++ _, _} -> ok
     after 1000 -> ct:fail(failed) end,
@@ -2524,7 +2524,7 @@ error_repair(Conf) when is_list(Conf) ->
 	disk_log:open([{name, n}, {file, File}, {type, wrap},
 		       {format, internal}, {size, {4000,No}}]),
     ok = disk_log:close(n),
-    true = (P2 == pps()),
+    check_pps(P2),
     del(File, No),
     receive {info_msg, _, "disk_log: repairing" ++ _, _} -> ok
     after 1000 -> ct:fail(failed) end,
@@ -2633,7 +2633,7 @@ error_log(Conf) when is_list(Conf) ->
     {ok, n} = disk_log:open([{name, n}, {file, File}, {type, wrap},
 			     {format, external},{size, {100, No}}]),
     {error, {file_error, _, _}} = disk_log:truncate(n),
-    true = (P0 == pps()),
+    check_pps(P0),
     del(File, No),
 
     %% OTP-4880.
@@ -2641,7 +2641,7 @@ error_log(Conf) when is_list(Conf) ->
     {ok, n} = disk_log:open([{name, n}, {file, File}, {type, halt},
 			     {format, external},{size, 100000}]),
     {error, {file_error, _, eisdir}} = disk_log:reopen(n, LDir),
-    true = (P0 == pps()),
+    check_pps(P0),
     file:delete(File),
 
     B = mk_bytes(60),
@@ -3003,7 +3003,7 @@ error_index(Conf) when is_list(Conf) ->
     {error, {invalid_index_file, _}} = disk_log:open(Args),
 
     del(File, No),
-    true = (P0 == pps()),
+    check_pps(P0),
     true = (Q == qlen()),
     ok.
 
@@ -4436,7 +4436,7 @@ dist_open2(Conf) when is_list(Conf) ->
 
     timer:sleep(500),
     file:delete(File),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     %% This time the first process has a naughty head_func. This test
     %% does not add very much. Perhaps it should be removed. However,
@@ -4482,7 +4482,7 @@ dist_open2(Conf) when is_list(Conf) ->
     timer:sleep(100),
     {error, no_such_log} = disk_log:close(Log),
     file:delete(File),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     No = 2,
     Log2 = n2,
@@ -4511,7 +4511,7 @@ dist_open2(Conf) when is_list(Conf) ->
 
     file:delete(File2),
     del(File, No),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     R.
     
@@ -4556,7 +4556,7 @@ dist_open2_1(Conf, Delay) ->
     {error, no_such_log} = disk_log:info(Log),
 
     file:delete(File),
-    true = (P0 == pps()),
+    check_pps(P0),
 
     ok.
 
@@ -4613,7 +4613,7 @@ dist_open2_2(Conf, Delay) ->
 	       {[{Node1,{repaired,_,_,_}}],[]}} -> ok
 	  end,
 
-    true = (P0 == pps()),
+    check_pps(P0),
     stop_node(Node1),
     file:delete(File),
     ok.
@@ -4791,10 +4791,59 @@ log(Name, N) ->
 format_error(E) ->
     lists:flatten(disk_log:format_error(E)).
 
+check_pps({Ports0,Procs0} = P0) ->
+    case pps() of
+        P0 ->
+            ok;
+        _ ->
+            timer:sleep(500),
+            case pps() of
+                P0 ->
+                    ok;
+                {Ports1,Procs1} = P1 ->
+		    case {Ports1 -- Ports0, Procs1 -- Procs0} of
+			{[], []} -> ok;
+			{PortsDiff,ProcsDiff} ->
+			    io:format("failure, got ~p~n, expected ~p\n", [P1, P0]),
+			    show("Old port", Ports0 -- Ports1),
+			    show("New port", PortsDiff),
+			    show("Old proc", Procs0 -- Procs1),
+			    show("New proc", ProcsDiff),
+			    ct:fail(failed)
+		    end
+	    end
+    end.
+
+show(_S, []) ->
+    ok;
+show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
+    io:format("~s: ~w (~w), ~w: ~p~n",
+              [S, Pid, proc_reg_name(Name), InitCall,
+               erlang:process_info(Pid)]),
+    show(S, Pids);
+show(S, [{Port, _}|Ports]) when is_port(Port)->
+    io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
+    show(S, Ports).
+
 pps() ->
     timer:sleep(100),
-    {erlang:ports(), lists:filter(fun(P) -> erlang:is_process_alive(P) end,
-				  processes())}.
+    {port_list(), process_list()}.
+
+port_list() ->
+    [{P,safe_second_element(erlang:port_info(P, name))} ||
+        P <- erlang:ports()].
+
+process_list() ->
+    [{P,process_info(P, registered_name),
+      safe_second_element(process_info(P, initial_call))} ||
+        P <- processes(), erlang:is_process_alive(P)].
+
+proc_reg_name({registered_name, Name}) -> Name;
+proc_reg_name([]) -> no_reg_name.
+
+safe_second_element({_,Info}) -> Info;
+safe_second_element(Other) -> Other.
+
 
 qlen() ->
     {_, {_, N}} = lists:keysearch(message_queue_len, 1, process_info(self())),
-- 
2.16.4

openSUSE Build Service is sponsored by