File 1004-Emulator-test-suite-Replace-use-of-random-with-rand.patch of Package erlang

From 71ddd8c1aba0478fe5aa07bdc8f9e6a86515bb11 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 9 Dec 2015 15:04:28 +0100
Subject: [PATCH 03/15] Emulator test suite: Replace use of 'random' with
 'rand'

---
 erts/emulator/test/binary_SUITE.erl         | 39 ++++++++++++------------
 erts/emulator/test/bs_bincomp_SUITE.erl     |  2 +-
 erts/emulator/test/decode_packet_SUITE.erl  | 47 ++++++++++++++---------------
 erts/emulator/test/driver_SUITE.erl         | 15 +++------
 erts/emulator/test/evil_SUITE.erl           |  4 +--
 erts/emulator/test/hash_SUITE.erl           | 10 +++---
 erts/emulator/test/map_SUITE.erl            | 27 ++++++++---------
 erts/emulator/test/nif_SUITE.erl            | 19 +++++-------
 erts/emulator/test/op_SUITE.erl             | 23 +++++++-------
 erts/emulator/test/port_SUITE.erl           | 15 +++++----
 erts/emulator/test/port_bif_SUITE.erl       |  9 +-----
 erts/emulator/test/random_iolist.erl        | 16 +++++-----
 erts/emulator/test/save_calls_SUITE.erl     |  4 +--
 erts/emulator/test/system_profile_SUITE.erl |  2 +-
 erts/emulator/test/time_SUITE.erl           | 36 ++++++++++------------
 erts/emulator/test/trace_SUITE.erl          |  4 +--
 16 files changed, 121 insertions(+), 151 deletions(-)

diff --git a/erts/emulator/test/binary_SUITE.erl b/erts/emulator/test/binary_SUITE.erl
index 96ba2f6..f8f71ef 100644
--- a/erts/emulator/test/binary_SUITE.erl
+++ b/erts/emulator/test/binary_SUITE.erl
@@ -521,30 +521,29 @@ external_size_1(Term, Size0, Limit) when Size0 < Limit ->
 external_size_1(_, _, _) -> ok.
 
 t_iolist_size(Config) when is_list(Config) ->
-    ?line Seed = {erlang:monotonic_time(),
-		  erlang:time_offset(),
-		  erlang:unique_integer([positive])},
-    ?line io:format("Seed: ~p", [Seed]),
-    ?line random:seed(Seed),
-    ?line Base = <<0:(1 bsl 20)/unit:8>>,
-    ?line Powers = [1 bsl N || N <- lists:seq(2, 37)],
-    ?line Sizes0 = [[N - random:uniform(N div 2),
-		     lists:seq(N-2, N+2),
-		     N+N div 2,
-		     N + random:uniform(N div 2)] ||
-		       N <- Powers],
+    _ = rand:uniform(),				%Seed generator
+    io:format("Seed: ~p", [rand:export_seed()]),
+
+    Base = <<0:(1 bsl 20)/unit:8>>,
+    Powers = [1 bsl N || N <- lists:seq(2, 37)],
+    Sizes0 = [[N - rand:uniform(N div 2),
+	       lists:seq(N-2, N+2),
+	       N+N div 2,
+	       N + rand:uniform(N div 2)] ||
+		 N <- Powers],
+
     %% Test sizes around 1^32 more thoroughly.
     FourGigs = 1 bsl 32,
-    ?line Sizes1 = [FourGigs+N || N <- lists:seq(-8, 40)] ++ Sizes0,
-    ?line Sizes2 = lists:flatten(Sizes1),
-    ?line Sizes = lists:usort(Sizes2),
+    Sizes1 = [FourGigs+N || N <- lists:seq(-8, 40)] ++ Sizes0,
+    Sizes2 = lists:flatten(Sizes1),
+    Sizes = lists:usort(Sizes2),
     io:format("~p sizes:", [length(Sizes)]),
     io:format("~p\n", [Sizes]),
-    ?line [Sz = iolist_size(build_iolist(Sz, Base)) || Sz <- Sizes],
+    _ = [Sz = iolist_size(build_iolist(Sz, Base)) || Sz <- Sizes],
     ok.
 
 build_iolist(N, Base) when N < 16 ->
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
 	    <<Bin:N/binary,_/binary>> = Base,
 	    Bin;
@@ -552,7 +551,7 @@ build_iolist(N, Base) when N < 16 ->
 	    lists:seq(1, N)
     end;
 build_iolist(N, Base) when N =< byte_size(Base) ->
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
 	    <<Bin:N/binary,_/binary>> = Base,
 	    Bin;
@@ -570,7 +569,7 @@ build_iolist(N, Base) when N =< byte_size(Base) ->
 	    end
     end;
 build_iolist(N0, Base) ->
-    Small = random:uniform(15),
+    Small = rand:uniform(15),
     Seq = lists:seq(1, Small),
     N = N0 - Small,
     case N rem 2 of
@@ -1604,7 +1603,7 @@ bit_sized_binary(Bin0) ->
 
 unaligned_sub_bin(Bin, 0) -> Bin;
 unaligned_sub_bin(Bin0, Offs) ->
-    F = random:uniform(256),
+    F = rand:uniform(256),
     Roffs = 8-Offs,
     Bin1 = <<F:Offs,Bin0/binary,F:Roffs>>,
     Sz = size(Bin0),
diff --git a/erts/emulator/test/bs_bincomp_SUITE.erl b/erts/emulator/test/bs_bincomp_SUITE.erl
index dcd13c1..8836fe4 100644
--- a/erts/emulator/test/bs_bincomp_SUITE.erl
+++ b/erts/emulator/test/bs_bincomp_SUITE.erl
@@ -131,7 +131,7 @@ tracing(Config) when is_list(Config) ->
 
 random_binary() ->
     Seq = [1,2,3,4,5,6,7,8,9,10],
-    << <<($a + random:uniform($z - $a)):8>> || _ <- Seq >>.
+    << <<($a + rand:uniform($z - $a)):8>> || _ <- Seq >>.
 
 random_binaries(N) when N > 0 ->
     random_binary(),
diff --git a/erts/emulator/test/decode_packet_SUITE.erl b/erts/emulator/test/decode_packet_SUITE.erl
index 6a5ca20..65ae94d 100644
--- a/erts/emulator/test/decode_packet_SUITE.erl
+++ b/erts/emulator/test/decode_packet_SUITE.erl
@@ -53,11 +53,8 @@ end_per_group(_GroupName, Config) ->
 
 
 init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
-    Seed = {S1,S2,S3} = {erlang:monotonic_time(),
-			 erlang:time_offset(),
-			 erlang:unique_integer()},
-    random:seed(S1,S2,S3),
-    io:format("*** SEED: ~p ***\n", [Seed]),
+    rand:seed(exsplus),
+    io:format("*** SEED: ~p ***\n", [rand:export_seed()]),
     Dog=?t:timetrap(?t:minutes(1)),
     [{watchdog, Dog}|Config].
 
@@ -136,7 +133,7 @@ pack(Type,Body,Rest,BitOffs) ->
     {Packet,Unpacked} = pack(Type,Body),
 
     %% Make Bin a sub-bin with an arbitrary bitoffset within Orig
-    Prefix = random:uniform(1 bsl BitOffs) - 1,
+    Prefix = rand:uniform(1 bsl BitOffs) - 1,
     Orig = <<Prefix:BitOffs,Packet/binary,Rest/bits>>,
     <<_:BitOffs,Bin/bits>> = Orig,
     {Bin,Unpacked,Orig}.
@@ -151,13 +148,13 @@ pack(4,Bin) ->
     Psz = byte_size(Bin),
     {<<Psz:32,Bin/binary>>, Bin};
 pack(asn1,Bin) ->
-    Ident = case random:uniform(3) of
+    Ident = case rand:uniform(3) of
 		1 -> <<17>>;
 		2 -> <<16#1f,16#81,17>>;
 		3 -> <<16#1f,16#81,16#80,16#80,17>>
 	    end,
     Psz = byte_size(Bin),
-    Length = case random:uniform(4) of
+    Length = case rand:uniform(4) of
 		 1 when Psz < 128 -> 
 		     <<Psz:8>>;
 		 R when R=<2 andalso Psz < 16#10000 ->
@@ -177,42 +174,42 @@ pack(sunrm,Bin) ->
     {Res,Res};
 pack(cdr,Bin) ->
     GIOP = <<"GIOP">>,
-    Major = random:uniform(256) - 1,
-    Minor = random:uniform(256) - 1,
-    MType = random:uniform(256) - 1,
+    Major = rand:uniform(256) - 1,
+    Minor = rand:uniform(256) - 1,
+    MType = rand:uniform(256) - 1,
     Psz = byte_size(Bin),
-    Res = case random:uniform(2) of 
+    Res = case rand:uniform(2) of
 	      1 -> <<GIOP/binary,Major:8,Minor:8,0:8,MType:8,Psz:32/big,Bin/binary>>;
 	      2 -> <<GIOP/binary,Major:8,Minor:8,1:8,MType:8,Psz:32/little,Bin/binary>>
 	  end,
     {Res,Res};
 pack(fcgi,Bin) ->
     Ver = 1,
-    Type = random:uniform(256) - 1,
-    Id = random:uniform(65536) - 1,
-    PaddSz = random:uniform(16) - 1,    
+    Type = rand:uniform(256) - 1,
+    Id = rand:uniform(65536) - 1,
+    PaddSz = rand:uniform(16) - 1,
     Psz = byte_size(Bin),
-    Reserv = random:uniform(256) - 1,
+    Reserv = rand:uniform(256) - 1,
     Padd = case PaddSz of
 	       0 -> <<>>;
-	       _ -> list_to_binary([random:uniform(256)-1
+	       _ -> list_to_binary([rand:uniform(256)-1
 				    || _<- lists:seq(1,PaddSz)])
 	   end,
     Res = <<Ver:8,Type:8,Id:16,Psz:16/big,PaddSz:8,Reserv:8,Bin/binary>>,
     {<<Res/binary,Padd/binary>>, Res};
 pack(tpkt,Bin) ->
     Ver = 3,
-    Reserv = random:uniform(256) - 1,
+    Reserv = rand:uniform(256) - 1,
     Size = byte_size(Bin) + 4,
     Res = <<Ver:8,Reserv:8,Size:16,Bin/binary>>,
     {Res, Res};
 pack(ssl_tls,Bin) ->
-    Content = case (random:uniform(256) - 1) of
+    Content = case (rand:uniform(256) - 1) of
 		  C when C<128 -> C;
 		  _ -> v2hello
 	      end,
-    Major = random:uniform(256) - 1,
-    Minor = random:uniform(256) - 1,
+    Major = rand:uniform(256) - 1,
+    Minor = rand:uniform(256) - 1,
     pack_ssl(Content,Major,Minor,Bin).
 
 pack_ssl(Content, Major, Minor, Body) ->
@@ -371,10 +368,10 @@ http_do({Bin,[{_Line,PL,PB}|Tail]}, Type) ->
     ?line {ok, PB, Rest} = decode_pkt(http_with_bin(Type),Bin),
 
     %% Same tests again but as SubBin
-    PreLen = random:uniform(64),
-    Prefix = random:uniform(1 bsl PreLen) - 1,
-    SufLen = random:uniform(64),
-    Suffix = random:uniform(1 bsl SufLen) - 1,
+    PreLen = rand:uniform(64),
+    Prefix = rand:uniform(1 bsl PreLen) - 1,
+    SufLen = rand:uniform(64),
+    Suffix = rand:uniform(1 bsl SufLen) - 1,
     Orig = <<Prefix:PreLen, Bin/bits, Suffix:SufLen>>,
     BinLen = bit_size(Bin),
     <<_:PreLen, SubBin:BinLen/bits, _/bits>> = Orig, % Make SubBin
diff --git a/erts/emulator/test/driver_SUITE.erl b/erts/emulator/test/driver_SUITE.erl
index b72d6cb..4fd7b36 100644
--- a/erts/emulator/test/driver_SUITE.erl
+++ b/erts/emulator/test/driver_SUITE.erl
@@ -224,7 +224,7 @@ outputv_errors_1(Term) ->
     port_close(Port).
 
 build_iolist(N, Base) when N < 16 ->
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
 	    <<Bin:N/binary,_/binary>> = Base,
 	    Bin;
@@ -232,7 +232,7 @@ build_iolist(N, Base) when N < 16 ->
 	    lists:seq(1, N)
     end;
 build_iolist(N, Base) when N =< byte_size(Base) ->
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
 	    <<Bin:N/binary,_/binary>> = Base,
 	    Bin;
@@ -250,7 +250,7 @@ build_iolist(N, Base) when N =< byte_size(Base) ->
 	    end
     end;
 build_iolist(N0, Base) ->
-    Small = random:uniform(15),
+    Small = rand:uniform(15),
     Seq = lists:seq(1, Small),
     N = N0 - Small,
     case N rem 2 of
@@ -2502,14 +2502,7 @@ random_char() ->
     uniform(256) - 1.
 
 uniform(N) ->
-    case get(random_seed) of
-	undefined ->
-	    {X, Y, Z} = time(),
-	    random:seed(X, Y, Z);
-	_ ->
-	    ok
-    end,
-    random:uniform(N).
+    rand:uniform(N).
 
 erl_millisecs() ->
     erl_millisecs(erlang:monotonic_time()).
diff --git a/erts/emulator/test/evil_SUITE.erl b/erts/emulator/test/evil_SUITE.erl
index 484d2a8..d28e4d9 100644
--- a/erts/emulator/test/evil_SUITE.erl
+++ b/erts/emulator/test/evil_SUITE.erl
@@ -382,10 +382,10 @@ my_appender_1(N, T0) ->
     my_appender_1(N-1, T).
     
 seed() ->
-    random:seed(3172, 9815, 20129).
+    rand:seed(exsplus, {3172,9815,20129}).
 
 rnd_term() ->
-    U0 = random:uniform(),
+    U0 = rand:uniform(),
     B = <<U0/float>>,
     {U0,U0 * 2.5 + 3.14,[U0*2.3,B]}.
 
diff --git a/erts/emulator/test/hash_SUITE.erl b/erts/emulator/test/hash_SUITE.erl
index 2ea4946..1b2acf4 100644
--- a/erts/emulator/test/hash_SUITE.erl
+++ b/erts/emulator/test/hash_SUITE.erl
@@ -223,11 +223,10 @@ basic_test() ->
 
 
 range_test() ->
-    random:seed(),
     F = fun(From,From,_FF) ->
 		ok;
 	   (From,To,FF) ->
-		R = random:uniform(16#FFFFFFFFFFFFFFFF),
+		R = rand:uniform(16#FFFFFFFFFFFFFFFF),
 		X = erlang:phash(R, From),
 		Y = erlang:phash(R, 16#100000000) - 1,
 		Z = (Y rem From) + 1,
@@ -265,14 +264,13 @@ spread_test(N) ->
 
 
 cmp_test(N) ->
-    % No need to save seed, the error indicates what number caused it.
-    random:seed(),
     do_cmp_hashes(N,8).
+
 do_cmp_hashes(0,_) ->
     ok;
 do_cmp_hashes(N,Steps) ->
-    R0 = random:uniform(1 bsl Steps - 1) + random:uniform(16#FFFFFFFF),
-    R = case random:uniform(2) of
+    R0 = rand:uniform(1 bsl Steps - 1) + rand:uniform(16#FFFFFFFF),
+    R = case rand:uniform(2) of
 	    1 ->
 		R0;
 	    _ ->
diff --git a/erts/emulator/test/map_SUITE.erl b/erts/emulator/test/map_SUITE.erl
index 6890c42..b74be7c 100644
--- a/erts/emulator/test/map_SUITE.erl
+++ b/erts/emulator/test/map_SUITE.erl
@@ -1511,11 +1511,8 @@ t_map_equal(Config) when is_list(Config) ->
 
 
 t_map_compare(Config) when is_list(Config) ->
-    Seed = {erlang:monotonic_time(),
-	    erlang:time_offset(),
-	    erlang:unique_integer()},
-    io:format("seed = ~p\n", [Seed]),
-    random:seed(Seed),
+    rand:seed(exsplus),
+    io:format("seed = ~p\n", [rand:export_seed()]),
     repeat(100, fun(_) -> float_int_compare() end, []),
     repeat(100, fun(_) -> recursive_compare() end, []),
     ok.
@@ -1533,7 +1530,7 @@ float_int_compare() ->
 
 numeric_keys(N) ->
     lists:foldl(fun(_,Acc) ->
-			Int = random:uniform(N*4) - N*2,
+			Int = rand:uniform(N*4) - N*2,
 			Float = float(Int),
 			[Int, Float, Float * 0.99, Float * 1.01 | Acc]
 		end,
@@ -1564,7 +1561,7 @@ do_compare([Gen1, Gen2]) ->
 
     %% Change one key from int to float (or vice versa) and check compare
     ML1 = maps:to_list(M1),
-    {K1,V1} = lists:nth(random:uniform(length(ML1)), ML1),
+    {K1,V1} = lists:nth(rand:uniform(length(ML1)), ML1),
     case K1 of
 	I when is_integer(I) ->
 	    case maps:find(float(I),M1) of
@@ -1655,9 +1652,9 @@ cmp_others(T1, T2, _) ->
 
 map_gen(Pairs, Size) ->
     {_,L} = lists:foldl(fun(_, {Keys, Acc}) ->
-				KI = random:uniform(size(Keys)),
+				KI = rand:uniform(size(Keys)),
 				K = element(KI,Keys),
-				KV = element(random:uniform(size(K)), K),
+				KV = element(rand:uniform(size(K)), K),
 				{erlang:delete_element(KI,Keys), [KV | Acc]}
 			end,
 			{Pairs, []},
@@ -1697,15 +1694,15 @@ term_gen_recursive(Leafs, Flags, Depth) ->
     MaxDepth = 10,
     Rnd = case {Flags, Depth} of
 	      {_, MaxDepth} -> % Only leafs
-		  random:uniform(size(Leafs)) + 3;
+		  rand:uniform(size(Leafs)) + 3;
 	      {0, 0} ->        % Only containers
-		  random:uniform(3);
+		  rand:uniform(3);
 	      {0,_} ->         % Anything
-		  random:uniform(size(Leafs)+3)
+		  rand:uniform(size(Leafs)+3)
 	  end,
     case Rnd of
 	1 -> % Make map
-	    Size = random:uniform(size(Leafs)),
+	    Size = rand:uniform(size(Leafs)),
 	    lists:foldl(fun(_, {Acc1,Acc2}) ->
 				{K1,K2} = term_gen_recursive(Leafs, Flags,
 							     Depth+1),
@@ -1720,7 +1717,7 @@ term_gen_recursive(Leafs, Flags, Depth) ->
 	    {Cdr1,Cdr2} = term_gen_recursive(Leafs, Flags, Depth+1),
 	    {[Car1 | Cdr1], [Car2 | Cdr2]};
 	3 -> % Make tuple
-	    Size = random:uniform(size(Leafs)),
+	    Size = rand:uniform(size(Leafs)),
 	    L = lists:map(fun(_) -> term_gen_recursive(Leafs, Flags, Depth+1) end,
 			  lists:seq(1,Size)),
 	    {L1, L2} = lists:unzip(L),
@@ -1729,7 +1726,7 @@ term_gen_recursive(Leafs, Flags, Depth) ->
 	N -> % Make leaf
 	    case element(N-3, Leafs) of
 		I when is_integer(I) ->
-		    case random:uniform(4) of
+		    case rand:uniform(4) of
 			1 -> {I, float(I)};
 			2 -> {float(I), I};
 			_ -> {I,I}
diff --git a/erts/emulator/test/nif_SUITE.erl b/erts/emulator/test/nif_SUITE.erl
index af2b955..56b36d2 100644
--- a/erts/emulator/test/nif_SUITE.erl
+++ b/erts/emulator/test/nif_SUITE.erl
@@ -1192,11 +1192,8 @@ send3(Config) when is_list(Config) ->
     %% Let a number of processes send random message blobs between each other
     %% using enif_send. Kill and spawn new ones randomly to keep a ~constant
     %% number of workers running.
-    Seed = {erlang:monotonic_time(),
-	    erlang:time_offset(),
-	    erlang:unique_integer()},
-    io:format("seed: ~p\n",[Seed]), 
-    random:seed(Seed),    
+    rand:seed(exsplus),
+    io:format("seed: ~p\n",[rand:export_seed()]),
     ets:new(nif_SUITE,[named_table,public]),
     ?line true = ets:insert(nif_SUITE,{send3,0,0,0,0}),
     timer:send_after(10000, timeout), % Run for 10 seconds
@@ -1229,7 +1226,7 @@ send3_controller(SpawnCnt0, Mons0, Pids0, Tick) ->
     after Tick -> 
         Max = 20,
         N = length(Pids0),
-        PidN = random:uniform(Max),
+        PidN = rand:uniform(Max),
         %%io:format("N=~p PidN=~p Pids0=~p\n", [N,PidN,Pids0]), 
         case PidN > N of
             true ->
@@ -1293,7 +1290,7 @@ send3_proc(Pids0, Counters={Rcv,SndOk,SndFail}, State0) ->
     end.
 
 send3_proc_send(Pids, {Rcv,SndOk,SndFail}, State0) ->
-    To = lists:nth(random:uniform(length(Pids)),Pids),
+    To = lists:nth(rand:uniform(length(Pids)),Pids),
     Blob = send3_make_blob(),
     State1 = send3_new_state(State0,Blob), 
     case send3_send(To, Blob) of
@@ -1305,12 +1302,12 @@ send3_proc_send(Pids, {Rcv,SndOk,SndFail}, State0) ->
 
 
 send3_make_blob() ->    
-    case random:uniform(20)-1 of
+    case rand:uniform(20)-1 of
         0 -> {term,[]};
         N ->
             MsgEnv = alloc_msgenv(), 
             repeat(N bsr 1,
-                   fun(_) -> grow_blob(MsgEnv,other_term(),random:uniform(1 bsl 20))
+                   fun(_) -> grow_blob(MsgEnv,other_term(),rand:uniform(1 bsl 20))
                    end, void),
             case (N band 1) of
                 0 -> {term,copy_blob(MsgEnv)};
@@ -1320,7 +1317,7 @@ send3_make_blob() ->
 
 send3_send(Pid, Msg) ->
     %% 90% enif_send and 10% normal bang
-    case random:uniform(10) of
+    case rand:uniform(10) of
         1 -> send3_send_bang(Pid,Msg);
         _ -> send3_send_nif(Pid,Msg)
     end.
@@ -1341,7 +1338,7 @@ send3_send_bang(Pid, {msgenv,MsgEnv}) ->
     true.
 
 send3_new_state(State, Blob) ->
-    case random:uniform(5+2) of
+    case rand:uniform(5+2) of
         N when N =< 5-> setelement(N, State, Blob);
         _ -> State  % Don't store blob
     end.
diff --git a/erts/emulator/test/op_SUITE.erl b/erts/emulator/test/op_SUITE.erl
index 6eda78a..65a5a4c 100644
--- a/erts/emulator/test/op_SUITE.erl
+++ b/erts/emulator/test/op_SUITE.erl
@@ -97,10 +97,11 @@ relop_simple(Config) when is_list(Config) ->
     lists:foreach(fun({A,B}) -> relop_simple_do(A,B) end,
 		  Combos),
 
-    repeat(fun() -> Size = random:uniform(100),
-		    Rnd1 = make_rand_term(Size),
-		    {Rnd2,0} = clone_and_mutate(Rnd1, random:uniform(Size)),
-		    relop_simple_do(Rnd1,Rnd2)
+    repeat(fun() ->
+		   Size = rand:uniform(100),
+		   Rnd1 = make_rand_term(Size),
+		   {Rnd2,0} = clone_and_mutate(Rnd1, rand:uniform(Size)),
+		   relop_simple_do(Rnd1,Rnd2)
 	   end,
 	   1000),
     ok.
@@ -158,7 +159,7 @@ cmp_emu(A,B) ->
 make_rand_term(1) ->
     make_rand_term_single();
 make_rand_term(Arity) ->
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
 	    make_rand_list(Arity);
 	2 ->
@@ -169,17 +170,17 @@ make_rand_term(Arity) ->
     end.
 
 make_rand_term_single() ->
-    Range = 1 bsl random:uniform(200),
-    case random:uniform(12) of
+    Range = 1 bsl rand:uniform(200),
+    case rand:uniform(12) of
 	1 -> random;
 	2 -> uniform;
-	3 -> random:uniform(Range) - (Range div 2);
-	4 -> Range * (random:uniform() - 0.5);
+	3 -> rand:uniform(Range) - (Range div 2);
+	4 -> Range * (rand:uniform() - 0.5);
 	5 -> 0;
 	6 -> 0.0;
 	7 -> make_ref();
 	8 -> self();
-	9 -> term_to_binary(random:uniform(Range));
+	9 -> term_to_binary(rand:uniform(Range));
 	10 -> fun(X) -> X*Range end; 
 	11 -> fun(X) -> X/Range end;
 	12 -> []
@@ -188,7 +189,7 @@ make_rand_term_single() ->
 make_rand_term_rand_size(1) ->
     {make_rand_term(1), 0};
 make_rand_term_rand_size(MaxArity) ->
-    Arity = random:uniform(MaxArity-1),
+    Arity = rand:uniform(MaxArity-1),
     {make_rand_term(Arity), MaxArity-Arity}.
 
 make_rand_list(0) -> [];
diff --git a/erts/emulator/test/port_SUITE.erl b/erts/emulator/test/port_SUITE.erl
index 3d0509a..b42e02a 100644
--- a/erts/emulator/test/port_SUITE.erl
+++ b/erts/emulator/test/port_SUITE.erl
@@ -2183,15 +2183,14 @@ random_char(Chars) ->
     lists:nth(uniform(length(Chars)), Chars).
 
 uniform(N) ->
-    case get(random_seed) of
-	undefined ->	    
-	    {X, Y, Z} = Seed = time(),
-	    io:format("Random seed = ~p\n",[Seed]),
-	    random:seed(X, Y, Z);
+    case rand:export_seed() of
+	undefined ->
+	    rand:seed(exsplus),
+	    io:format("Random seed = ~p\n", [rand:export_seed()]);
 	_ ->
 	    ok
     end,
-    random:uniform(N).
+    rand:uniform(N).
 
 fun_spawn(Fun) ->
     fun_spawn(Fun, []).
@@ -2331,7 +2330,7 @@ close_deaf_port(Config) when is_list(Config) ->
 close_deaf_port_1(200, _) ->
     ok;
 close_deaf_port_1(N, Cmd) ->
-    Timeout = integer_to_list(random:uniform(5*1000)),
+    Timeout = integer_to_list(rand:uniform(5*1000)),
     try open_port({spawn_executable,Cmd},[{args,[Timeout]}]) of
     	Port ->
 	    erlang:port_command(Port,"Hello, can you hear me!?!?"),
@@ -2372,7 +2371,7 @@ port_setget_data(Config) when is_list(Config) ->
     ok.
 
 port_setget_data_hammer(Port, HeapData, IsSet0, N) ->
-    Rand = random:uniform(3),
+    Rand = rand:uniform(3),
     IsSet1 = try case Rand of
 		     1 -> true = erlang:port_set_data(Port, atom), true;
 		     2 -> true = erlang:port_set_data(Port, HeapData), true;
diff --git a/erts/emulator/test/port_bif_SUITE.erl b/erts/emulator/test/port_bif_SUITE.erl
index b65a22a..981899b 100644
--- a/erts/emulator/test/port_bif_SUITE.erl
+++ b/erts/emulator/test/port_bif_SUITE.erl
@@ -485,14 +485,7 @@ random_char(Chars) ->
     lists:nth(uniform(length(Chars)), Chars).
 
 uniform(N) ->
-    case get(random_seed) of
-	undefined ->
-	    {X, Y, Z} = time(),
-	    random:seed(X, Y, Z);
-	_ ->
-	    ok
-    end,
-    random:uniform(N).
+    rand:uniform(N).
 
 unaligned_sub_bin(Bin0) ->
     Bin1 = <<0:3,Bin0/binary,31:5>>,
diff --git a/erts/emulator/test/random_iolist.erl b/erts/emulator/test/random_iolist.erl
index 9a0f034..6da7da0 100644
--- a/erts/emulator/test/random_iolist.erl
+++ b/erts/emulator/test/random_iolist.erl
@@ -36,7 +36,7 @@ run2(Iter,Fun1,Fun2) ->
     compare2(Iter,Fun1,Fun2).
 
 random_byte() ->
-     random:uniform(256) - 1.
+     rand:uniform(256) - 1.
 
 random_list(0,Acc) ->
     Acc;
@@ -45,7 +45,7 @@ random_list(N,Acc) ->
 
 random_binary(N) ->
     B = list_to_binary(random_list(N,[])),
-    case {random:uniform(2),size(B)} of
+    case {rand:uniform(2),size(B)} of
 	{2,M} when M > 1 ->
 	    S = M-1,
 	    <<_:3,C:S/binary,_:5>> = B,
@@ -57,7 +57,7 @@ random_list(N) ->
     random_list(N,[]).
 
 front() ->
-    case random:uniform(10) of
+    case rand:uniform(10) of
 	10 ->
 	    false;
 	_ ->
@@ -65,7 +65,7 @@ front() ->
     end.
 
 any_type() ->
-    case random:uniform(10) of
+    case rand:uniform(10) of
 	1 ->
 	    list;
 	2 ->
@@ -77,7 +77,7 @@ any_type() ->
     end.
 
 tail_type() ->
-    case random:uniform(5) of
+    case rand:uniform(5) of
 	1 ->
 	    list;
 	2 ->
@@ -90,9 +90,9 @@ random_length(N) ->
     UpperLimit = 255,
     case N of
 	M when M > UpperLimit ->
-	    random:uniform(UpperLimit+1) - 1;
+	    rand:uniform(UpperLimit+1) - 1;
 	_ ->
-	    random:uniform(N+1) - 1
+	    rand:uniform(N+1) - 1
     end.
 
 random_iolist(0,Acc) ->
@@ -139,7 +139,7 @@ random_iolist(N) ->
     
 
 standard_seed() ->
-    random:seed(1201,855653,380975).
+    rand:seed(exsplus, {1201,855653,380975}).
 
 do_comp(List,F1,F2) ->
     X = F1(List),
diff --git a/erts/emulator/test/save_calls_SUITE.erl b/erts/emulator/test/save_calls_SUITE.erl
index 544d841..810bc07 100644
--- a/erts/emulator/test/save_calls_SUITE.erl
+++ b/erts/emulator/test/save_calls_SUITE.erl
@@ -189,7 +189,7 @@ is_local_function(_) ->
 
 % Number crunching for reds test.
 carmichaels_below(N) ->
-    random:seed(3172,9814,20125),
+    rand:seed(exsplus, {3172,9814,20125}),
     carmichaels_below(1,N).
 
 carmichaels_below(N,N2) when N >= N2 ->
@@ -219,7 +219,7 @@ expmod(Base,Exp,Mod) ->
     (Base * expmod(Base,Exp - 1,Mod)) rem Mod.
 
 uniform(N) ->
-    random:uniform(N-1).
+    rand:uniform(N-1).
 
 fermat(N) ->    
     R = uniform(N),
diff --git a/erts/emulator/test/system_profile_SUITE.erl b/erts/emulator/test/system_profile_SUITE.erl
index e4b6511..0a07843 100644
--- a/erts/emulator/test/system_profile_SUITE.erl
+++ b/erts/emulator/test/system_profile_SUITE.erl
@@ -448,7 +448,7 @@ run_load(N, Pids) ->
     run_load(N - 1, [Pid | Pids]).
 
 list_load() -> 
-    ok = case math:sin(random:uniform(32451)) of
+    ok = case math:sin(rand:uniform(32451)) of
     	A when is_float(A) -> ok;
 	_ -> ok
     end,
diff --git a/erts/emulator/test/time_SUITE.erl b/erts/emulator/test/time_SUITE.erl
index 33076c7..3bd28a6 100644
--- a/erts/emulator/test/time_SUITE.erl
+++ b/erts/emulator/test/time_SUITE.erl
@@ -69,7 +69,7 @@
 init_per_testcase(Func, Config) when is_atom(Func), is_list(Config) ->
     [{testcase, Func}|Config].
 
-end_per_testcase(_Func, Config) ->
+end_per_testcase(_Func, _Config) ->
     ok.
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -742,25 +742,21 @@ chk_strc(Res0, Res1) ->
     ok.
 
 chk_random_values(FR, TR) ->
-%    case (FR rem TR == 0) orelse (TR rem FR == 0) of
-%	true ->
-	    io:format("rand values ~p -> ~p~n", [FR, TR]),
-	    random:seed(268438039, 268440479, 268439161),
-	    Values = lists:map(fun (_) -> random:uniform(1 bsl 65) - (1 bsl 64) end,
-			       lists:seq(1, 100000)),
-	    CheckFun = fun (V) ->
-			       CV = erlang:convert_time_unit(V, FR, TR),
-			       case {(FR*CV) div TR =< V,
-				     (FR*(CV+1)) div TR >= V} of
-				   {true, true} ->
-				       ok;
-				   Failure ->
-				       ?t:fail({Failure, CV, V, FR, TR})
-			       end
-		       end,
-	    lists:foreach(CheckFun, Values).%;
-%	false -> ok
-%    end.
+    io:format("rand values ~p -> ~p~n", [FR, TR]),
+    rand:seed(exsplus, {268438039,268440479,268439161}),
+    Values = lists:map(fun (_) -> rand:uniform(1 bsl 65) - (1 bsl 64) end,
+		       lists:seq(1, 100000)),
+    CheckFun = fun (V) ->
+		       CV = erlang:convert_time_unit(V, FR, TR),
+		       case {(FR*CV) div TR =< V,
+			     (FR*(CV+1)) div TR >= V} of
+			   {true, true} ->
+			       ok;
+			   Failure ->
+			       ?t:fail({Failure, CV, V, FR, TR})
+		       end
+	       end,
+    lists:foreach(CheckFun, Values).
 		       
 
 chk_values_per_value(_FromRes, _ToRes,
diff --git a/erts/emulator/test/trace_SUITE.erl b/erts/emulator/test/trace_SUITE.erl
index 6eae182..00b90e3 100644
--- a/erts/emulator/test/trace_SUITE.erl
+++ b/erts/emulator/test/trace_SUITE.erl
@@ -933,7 +933,7 @@ suspend_exit(suite) ->
     [];
 suspend_exit(Config) when is_list(Config) ->
     ?line Dog = test_server:timetrap(test_server:minutes(2)),
-    ?line random:seed(4711,17,4711),
+    rand:seed(exsplus, {4711,17,4711}),
     ?line do_suspend_exit(5000),
     ?line test_server:timetrap_cancel(Dog),
     ?line ok.
@@ -941,7 +941,7 @@ suspend_exit(Config) when is_list(Config) ->
 do_suspend_exit(0) ->
     ?line ok;
 do_suspend_exit(N) ->
-    ?line Work = random:uniform(50),
+    Work = rand:uniform(50),
     ?line Parent = self(),
     ?line {Suspendee, Mon2}
 	= spawn_monitor(fun () ->
-- 
2.1.4

openSUSE Build Service is sponsored by