File 1011-system-tests-Replace-random-with-rand.patch of Package erlang

From 5850300f41de8047b9a9da1e4f00aaee3dcd662c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 10 Dec 2015 12:40:40 +0100
Subject: [PATCH 11/15] system tests: Replace 'random' with 'rand'

---
 erts/test/ethread_SUITE.erl | 32 --------------------------------
 erts/test/run_erl_SUITE.erl | 18 ++++++++----------
 2 files changed, 8 insertions(+), 42 deletions(-)

diff --git a/erts/test/ethread_SUITE.erl b/erts/test/ethread_SUITE.erl
index 4a40dbb..388af66 100644
--- a/erts/test/ethread_SUITE.erl
+++ b/erts/test/ethread_SUITE.erl
@@ -123,38 +123,6 @@ try_lock_mutex(suite) ->
 try_lock_mutex(Config) ->
     run_case(Config, "try_lock_mutex", "").
 
-%% Remove dead code?
-
-% wd_dispatch(P) ->
-%     receive
-% 	bye ->
-% 	    ?line true = port_command(P, "-1 "),
-% 	    ?line bye;
-% 	L when is_list(L) ->
-% 	    ?line true = port_command(P, L),
-% 	    ?line wd_dispatch(P)
-%     end.
-% 
-% watchdog(Port) ->
-%     ?line process_flag(priority, max),
-%     ?line receive after 500 -> ok end,
-% 
-%     ?line random:seed(),
-%     ?line true = port_command(Port, "0 "),
-%     ?line lists:foreach(fun (T) ->
-% 				erlang:send_after(T,
-% 						  self(),
-% 						  integer_to_list(T)
-% 						  ++ " ")
-% 			end,
-% 			lists:usort(lists:map(fun (_) ->
-% 						      random:uniform(4500)+500
-% 					      end,
-% 					      lists:duplicate(50,0)))),
-%     ?line erlang:send_after(5100, self(), bye),
-% 
-%     wd_dispatch(Port).
-
 cond_wait(doc) ->
     ["Tests ethr_cond_wait with ethr_cond_signal and ethr_cond_broadcast."];
 cond_wait(suite) ->
diff --git a/erts/test/run_erl_SUITE.erl b/erts/test/run_erl_SUITE.erl
index 328477d..6759d41 100644
--- a/erts/test/run_erl_SUITE.erl
+++ b/erts/test/run_erl_SUITE.erl
@@ -141,12 +141,10 @@ heavier_1(Config) ->
 
     ?line ToErl = open_port({spawn,"to_erl "++Pipe}, []),
     io:format("ToErl = ~p\n", [ToErl]),
-    X = 1,
-    Y = 555,
-    Z = 42,
-    ?line random:seed(X, Y, Z),
-    SeedCmd = lists:flatten(io_lib:format("random:seed(~p, ~p, ~p). \r\n",
-					  [X,Y,Z])),
+    Seed = {1,555,42},
+    rand:seed(exsplus, Seed),
+    SeedCmd = lists:flatten(io_lib:format("rand:seed(exsplus, ~p). \r\n",
+					  [Seed])),
     ?line io:format("~p\n", [SeedCmd]),
     ?line erlang:port_command(ToErl, SeedCmd),
 
@@ -157,9 +155,9 @@ heavier_1(Config) ->
 	"F = fun(F,0) -> ok; "++
 	       "(F,N) -> " ++
 	           "io:format(\"\\\"~s\\\"~n\","++
-	                     "[[35|[random:uniform(25)+65 || " ++
+	                     "[[35|[rand:uniform(25)+65 || " ++
 	                     "_ <- lists:seq(1, "++
-	                                "random:uniform("++
+	                                "rand:uniform("++
                                              integer_to_list(MaxLen)++
                                         "))]]]), "++
 	           "F(F,N-1) "++
@@ -189,8 +187,8 @@ receive_all(Iter, ToErl, MaxLen) ->
 
 receive_all_1(0, _, _, _) -> ok;
 receive_all_1(Iter, Line, ToErl, MaxLen) ->
-    NumChars = random:uniform(MaxLen),
-    Pattern = [random:uniform(25)+65 || _ <- lists:seq(1, NumChars)],
+    NumChars = rand:uniform(MaxLen),
+    Pattern = [rand:uniform(25)+65 || _ <- lists:seq(1, NumChars)],
     receive_all_2(Iter, {NumChars,Pattern}, Line, ToErl, MaxLen).
     
 
-- 
2.1.4

openSUSE Build Service is sponsored by