File 1008-stdlib-tests-Replace-random-with-rand.patch of Package erlang

From 4145a6e4a5a65b1ba070328b03b8a0c085d9feba Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 9 Dec 2015 15:41:28 +0100
Subject: [PATCH 07/15] stdlib tests: Replace 'random' with 'rand'

---
 lib/stdlib/test/base64_SUITE.erl        |  2 +-
 lib/stdlib/test/binary_module_SUITE.erl | 34 +++++++-------
 lib/stdlib/test/dict_SUITE.erl          | 16 +++----
 lib/stdlib/test/ets_SUITE.erl           | 80 ++++++++++++++++-----------------
 lib/stdlib/test/ets_tough_SUITE.erl     | 10 ++---
 lib/stdlib/test/filelib_SUITE.erl       |  2 +-
 lib/stdlib/test/lists_SUITE.erl         | 22 +++------
 lib/stdlib/test/queue_SUITE.erl         | 10 ++---
 lib/stdlib/test/random_iolist.erl       | 16 +++----
 lib/stdlib/test/random_unicode_list.erl | 18 ++++----
 lib/stdlib/test/run_pcre_tests.erl      | 10 ++---
 lib/stdlib/test/select_SUITE.erl        | 21 +++++----
 lib/stdlib/test/sets_SUITE.erl          | 22 ++++-----
 lib/stdlib/test/timer_SUITE.erl         | 24 +++++-----
 14 files changed, 134 insertions(+), 153 deletions(-)

diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl
index 75eebba..f750145 100644
--- a/lib/stdlib/test/base64_SUITE.erl
+++ b/lib/stdlib/test/base64_SUITE.erl
@@ -340,7 +340,7 @@ interleaved_ws_roundtrip_1([], Base64List, Bin, List) ->
 random_byte_list(0, Acc) ->
     Acc;
 random_byte_list(N, Acc) -> 
-    random_byte_list(N-1, [random:uniform(255)|Acc]).
+    random_byte_list(N-1, [rand:uniform(255)|Acc]).
 
 make_big_binary(N) ->
     list_to_binary(mbb(N, [])).
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 933c3ce..8a2df2b 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -716,7 +716,7 @@ do_interesting(Module) ->
 encode_decode(doc) ->
     ["test binary:encode_unsigned/1,2 and binary:decode_unsigned/1,2"];
 encode_decode(Config) when is_list(Config) ->
-    ?line random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     ?line ok = encode_decode_loop({1,200},1000), % Need to be long enough
 						 % to create offheap binaries
     ok.
@@ -823,7 +823,7 @@ copy(Config) when is_list(Config) ->
     ?line badarg = ?MASK_ERROR(binary:copy(<<1,2,3>>,
 					   16#FFFFFFFFFFFFFFFFFFFFFFFFFFFFFF)),
     ?line <<>> = binary:copy(<<>>,10000),
-    ?line random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     ?line ok = random_copy(3000),
     ?line erts_debug:set_internal_state(available_internal_state,true),
     ?line io:format("oldlimit: ~p~n",
@@ -861,7 +861,7 @@ random_copy(0) ->
     ok;
 random_copy(N) ->
     Str = random_string({0,N}),
-    Num = random:uniform(N div 10+1),
+    Num = rand:uniform(N div 10+1),
     A = ?MASK_ERROR(binary:copy(Str,Num)),
     B = ?MASK_ERROR(binref:copy(Str,Num)),
     C = ?MASK_ERROR(binary:copy(make_unaligned(Str),Num)),
@@ -902,7 +902,7 @@ bin_to_list(Config) when is_list(Config) ->
     ?line [5] = lists:nthtail(byte_size(X)-1,LX),
     ?line [0,5] = lists:nthtail(byte_size(X)-2,LX),
     ?line [0,5] = lists:nthtail(byte_size(Y)-2,LY),
-    ?line random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     ?line ok = random_bin_to_list(5000),
     ok.
 
@@ -969,7 +969,7 @@ parts(Config) when is_list(Config) ->
     ?line badarg = ?MASK_ERROR(binary:part(Simple,{-1,0})),
     ?line badarg = ?MASK_ERROR(binary:part(Simple,{7,2})),
     ?line <<8>> = binary:part(Simple,{7,1}),
-    ?line random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     ?line random_parts(5000),
     ok.
 
@@ -993,15 +993,15 @@ random_parts(N) ->
 random_parts(0,_) ->
     [];
 random_parts(X,N) ->
-    Pos = random:uniform(N),
-    Len = random:uniform((Pos * 12) div 10),
+    Pos = rand:uniform(N),
+    Len = rand:uniform((Pos * 12) div 10),
     [{Pos,Len} | random_parts(X-1,N)].
 
 random_ref_comp(doc) ->
     ["Test pseudorandomly generated cases against reference imlementation"];
 random_ref_comp(Config) when is_list(Config) ->
     put(success_counter,0),
-    random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     Nr = {1,40},
     Hr = {30,1000},
     I1 = 1500,
@@ -1031,7 +1031,7 @@ random_ref_sr_comp(doc) ->
     ["Test pseudorandomly generated cases against reference imlementation of split and replace"];
 random_ref_sr_comp(Config) when is_list(Config) ->
     put(success_counter,0),
-    random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     Nr = {1,40},
     Hr = {30,1000},
     I1 = 1500,
@@ -1049,7 +1049,7 @@ random_ref_fla_comp(doc) ->
     ["Test pseudorandomly generated cases against reference imlementation of split and replace"];
 random_ref_fla_comp(Config) when is_list(Config) ->
     ?line put(success_counter,0),
-    ?line random:seed({1271,769940,559934}),
+    rand:seed(exsplus, {1271,769940,559934}),
     ?line do_random_first_comp(5000,{1,1000}),
     ?line do_random_last_comp(5000,{1,1000}),
     ?line do_random_at_comp(5000,{1,1000}),
@@ -1383,24 +1383,24 @@ one_random(N) ->
 
 random_number({Min,Max}) -> % Min and Max are *length* of number in
                             % decimal positions
-    X = random:uniform(Max - Min + 1) + Min - 1,
-    list_to_integer([one_random_number(random:uniform(10)) || _ <- lists:seq(1,X)]).
+    X = rand:uniform(Max - Min + 1) + Min - 1,
+    list_to_integer([one_random_number(rand:uniform(10)) || _ <- lists:seq(1,X)]).
 
 
 random_length({Min,Max}) ->
-    random:uniform(Max - Min + 1) + Min - 1.
+    rand:uniform(Max - Min + 1) + Min - 1.
 random_string({Min,Max}) ->
-    X = random:uniform(Max - Min + 1) + Min - 1,
-    list_to_binary([one_random(random:uniform(68)) || _ <- lists:seq(1,X)]).
+    X = rand:uniform(Max - Min + 1) + Min - 1,
+    list_to_binary([one_random(rand:uniform(68)) || _ <- lists:seq(1,X)]).
 random_substring({Min,Max},Hay) ->
-    X = random:uniform(Max - Min + 1) + Min - 1,
+    X = rand:uniform(Max - Min + 1) + Min - 1,
     Y = byte_size(Hay),
     Z = if
 	    X > Y -> Y;
 	    true -> X
 	end,
     PMax = Y - Z,
-    Pos = random:uniform(PMax + 1) - 1,
+    Pos = rand:uniform(PMax + 1) - 1,
     <<_:Pos/binary,Res:Z/binary,_/binary>> = Hay,
     Res.
 
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 648154e..aff73b1 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -108,7 +108,7 @@ iterate_1(M) ->
     M(empty, []).
 
 iterate_2(M) ->
-    random:seed(1, 2, 42),
+    rand:seed(exsplus, {1,2,42}),
     iter_tree(M, 1000).
 
 iter_tree(_M, 0) ->
@@ -117,7 +117,7 @@ iter_tree(M, N) ->
     L = [{I, I} || I <- lists:seq(1, N)],
     T = M(from_list, L),
     L = lists:reverse(iterate_tree(M, T)),
-    R = random:uniform(N),
+    R = rand:uniform(N),
     KV = lists:reverse(iterate_tree_from(M, R, T)),
     KV = [P || P={K,_} <- L, K >= R],
     iter_tree(M, N-1).
@@ -156,7 +156,7 @@ test_all(Tester) ->
 spawn_tester(M, Tester) ->
     Parent = self(),
     spawn_link(fun() ->
-		       random:seed(1, 2, 42),
+		       rand:seed(exsplus, {1,2,42}),
 		       S = Tester(M),
 		       Res = {M(size, S),lists:sort(M(to_list, S))},
 		       Parent ! {result,self(),Res}
@@ -194,12 +194,12 @@ rnd_list_1(0, Acc) ->
     Acc;
 rnd_list_1(N, Acc) ->
     Key = atomic_rnd_term(),
-    Value = random:uniform(100),
+    Value = rand:uniform(100),
     rnd_list_1(N-1, [{Key,Value}|Acc]).
 
 atomic_rnd_term() ->
-    case random:uniform(3) of
-	 1 -> list_to_atom(integer_to_list($\s+random:uniform(94))++"rnd");
-	 2 -> random:uniform();
-	 3 -> random:uniform(50)-37
+    case rand:uniform(3) of
+	 1 -> list_to_atom(integer_to_list($\s+rand:uniform(94))++"rnd");
+	 2 -> rand:uniform();
+	 3 -> rand:uniform(50)-37
     end.
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 1b80f55..3e63d19 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -112,9 +112,8 @@
 -define(m(A,B), ?line assert_eq(A,B)).
 
 init_per_testcase(Case, Config) ->
-    Seed = {S1,S2,S3} = random:seed0(), %now(),
-    random:seed(S1,S2,S3),
-    io:format("*** SEED: ~p ***\n", [Seed]),
+    rand:seed(exsplus),
+    io:format("*** SEED: ~p ***\n", [rand:export_seed()]),
     start_spawn_logger(),
     wait_for_test_procs(), %% Ensure previous case cleaned up
     Dog=test_server:timetrap(test_server:minutes(20)),
@@ -1330,7 +1329,7 @@ drop_match() ->
 
 
 ets_match(Tab,Expr) ->
-    case random:uniform(2) of
+    case rand:uniform(2) of
 	1 ->
 	    ets:match(Tab,Expr);
 	_ ->
@@ -1339,14 +1338,14 @@ ets_match(Tab,Expr) ->
 
 match_chunked(Tab,Expr) ->
     match_chunked_collect(ets:match(Tab,Expr,
-				    random:uniform(1999) + 1)).
+				    rand:uniform(1999) + 1)).
 match_chunked_collect('$end_of_table') ->
     [];
 match_chunked_collect({Results, Continuation}) ->
     Results ++ match_chunked_collect(ets:match(Continuation)).
 
 ets_match_object(Tab,Expr) ->
-    case random:uniform(2) of
+    case rand:uniform(2) of
 	1 ->
 	    ets:match_object(Tab,Expr);
 	_ ->
@@ -1355,7 +1354,7 @@ ets_match_object(Tab,Expr) ->
 
 match_object_chunked(Tab,Expr) ->
     match_object_chunked_collect(ets:match_object(Tab,Expr,
-						  random:uniform(1999) + 1)).
+						  rand:uniform(1999) + 1)).
 match_object_chunked_collect('$end_of_table') ->
     [];
 match_object_chunked_collect({Results, Continuation}) ->
@@ -1367,19 +1366,15 @@ random_test() ->
     ?line ReadDir = get(where_to_read),
     ?line WriteDir = get(where_to_write),
     ?line (catch file:make_dir(WriteDir)),
-    ?line Seed = case file:consult(filename:join([ReadDir, 
-					    "preset_random_seed.txt"])) of
-	       {ok,[X]} ->
-		   X;
-	       _ ->
-		   {A,B,C} = erlang:timestamp(),
-		   random:seed(A,B,C),
-		   get(random_seed)
-	   end,
-    put(random_seed,Seed),
-    ?line {ok, F} = file:open(filename:join([WriteDir, 
-					     "last_random_seed.txt"]), 
-			      [write]),
+    case file:consult(filename:join([ReadDir,"preset_random_seed.txt"])) of
+	{ok,[X]} ->
+	    rand:seed(X);
+	_ ->
+	    rand:seed(exsplus)
+    end,
+    Seed = rand:export_seed(),
+    {ok,F} = file:open(filename:join([WriteDir,"last_random_seed.txt"]),
+			[write]),
     io:format(F,"~p. ~n",[Seed]),
     file:close(F),
     io:format("Random seed ~p written to ~s, copy to ~s to rerun with "
@@ -1401,7 +1396,7 @@ do_random_test() ->
 	       end, 5000),
     ?line io:format("~nData inserted~n"),
     ?line do_n_times(fun() ->
-		       ?line I = random:uniform(25),
+		       I = rand:uniform(25),
 		       ?line Key = create_random_string(I) ++ '_',
 		       ?line L1 = ets_match_object(OrdSet,{Key,'_'}),
 		       ?line L2 = lists:sort(ets_match_object(Set,{Key,'_'})),
@@ -1961,7 +1956,7 @@ evil_update_counter(Config) when is_list(Config) ->
     gb_sets:module_info(),
     math:module_info(),
     ordsets:module_info(),
-    random:module_info(),
+    rand:module_info(),
 
     repeat_for_opts(evil_update_counter_do).
 
@@ -1995,7 +1990,7 @@ evil_counter(I,Opts) ->
 		1 -> 16#12345678FFFFFFFF;
 		2 -> 16#7777777777FFFFFFFF863648726743
 	    end,
-    Start = Start0 + random:uniform(100000),
+    Start = Start0 + rand:uniform(100000),
     ets:insert(T, {dracula,Start}),
     Iter = 40000,
     End = Start + Iter,
@@ -4645,11 +4640,11 @@ create_random_string(0) ->
     [];
 
 create_random_string(OfLength) ->
-    C = case random:uniform(2) of
+    C = case rand:uniform(2) of
 	1 ->
-	    (random:uniform($Z - $A + 1) - 1) + $A;
+	    (rand:uniform($Z - $A + 1) - 1) + $A;
 	_ ->
-	    (random:uniform($z - $a + 1) - 1) + $a
+	    (rand:uniform($z - $a + 1) - 1) + $a
 	end,
     [C | create_random_string(OfLength - 1)].
 
@@ -4660,7 +4655,7 @@ create_random_tuple(OfLength) ->
 			    end,create_random_string(OfLength))).
 
 create_partly_bound_tuple(OfLength) ->
-    case random:uniform(2) of
+    case rand:uniform(2) of
 	1 ->
 	   create_partly_bound_tuple1(OfLength); 
 	_ ->
@@ -4669,14 +4664,14 @@ create_partly_bound_tuple(OfLength) ->
 
 create_partly_bound_tuple1(OfLength) ->
     T0 = create_random_tuple(OfLength),
-    I = random:uniform(OfLength),
+    I = rand:uniform(OfLength),
     setelement(I,T0,'$1').
 
 
 set_n_random_elements(T0,0,_,_) ->
     T0;
 set_n_random_elements(T0,N,OfLength,GenFun) ->
-    I = random:uniform(OfLength),
+    I = rand:uniform(OfLength),
     What = GenFun(I),
     case element(I,T0) of
 	What ->
@@ -4690,12 +4685,12 @@ make_dollar_atom(I) ->
     list_to_atom([$$] ++ integer_to_list(I)).
 create_partly_bound_tuple2(OfLength) ->
     T0 = create_random_tuple(OfLength),
-    I = random:uniform(OfLength - 1),
+    I = rand:uniform(OfLength - 1),
     set_n_random_elements(T0,I,OfLength,fun make_dollar_atom/1).
 
 create_partly_bound_tuple3(OfLength) ->
     T0 = create_random_tuple(OfLength),
-    I = random:uniform(OfLength - 1),
+    I = rand:uniform(OfLength - 1),
     set_n_random_elements(T0,I,OfLength,fun(_) -> '_' end).
 
 do_n_times(_,0) ->
@@ -5058,11 +5053,12 @@ meta_wb_do(Opts) ->
 
     io:format("Colliding names = ~p\n",[Names]),
     F = fun(0,_,_) -> ok;
-	   (N,Tabs,Me) -> Name1 = lists:nth(random:uniform(Len),Names), 
-			  Name2 = lists:nth(random:uniform(Len),Names), 
-			  Op = element(random:uniform(3),OpFuns),
-			  NTabs = Op(Name1, Name2, Tabs, Opts),
-			  Me(N-1,NTabs,Me) 
+	   (N,Tabs,Me) ->
+		Name1 = lists:nth(rand:uniform(Len), Names),
+		Name2 = lists:nth(rand:uniform(Len), Names),
+		Op = element(rand:uniform(3),OpFuns),
+		NTabs = Op(Name1, Name2, Tabs, Opts),
+		Me(N-1, NTabs, Me)
 	end,
     F(Len*100, [], F),
 
@@ -5328,7 +5324,7 @@ smp_insert(suite) -> [];
 smp_insert(Config) when is_list(Config) ->
     ets_new(smp_insert,[named_table,public,{write_concurrency,true}]),
     InitF = fun(_) -> ok end,
-    ExecF = fun(_) -> true = ets:insert(smp_insert,{random:uniform(10000)})
+    ExecF = fun(_) -> true = ets:insert(smp_insert,{rand:uniform(10000)})
 	    end,
     FiniF = fun(_) -> ok end,
     run_workers(InitF,ExecF,FiniF,100000),
@@ -5579,10 +5575,10 @@ smp_select_delete(Config) when is_list(Config) ->
     Zeros = erlang:make_tuple(Mod,0),
     InitF = fun(_) -> Zeros end,
     ExecF = fun(Diffs0) -> 
-		    case random:uniform(20) of
+		    case rand:uniform(20) of
 			1 ->
 			    Mod = 17,
-			    Eq = random:uniform(Mod) - 1,
+			    Eq = rand:uniform(Mod) - 1,
 			    Deleted = ets:select_delete(T,
 							[{{'_', '$1'},
 							  [{'=:=', {'rem', '$1', Mod}, Eq}],
@@ -5591,7 +5587,7 @@ smp_select_delete(Config) when is_list(Config) ->
 						element(Eq+1,Diffs0) - Deleted),
 			    Diffs1;
 			_ ->
-			    Key = random:uniform(10000),
+			    Key = rand:uniform(10000),
 			    Eq = Key rem Mod,
 			    ?line case ets:insert_new(T,{Key,Key}) of
 				      true ->
@@ -5795,7 +5791,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
 			   N when (N > Exclude) -> N - Exclude
 		       end,
     io:format("smp starting ~p workers\n",[NumOfProcs]),
-    Seeds = [{ProcN,random:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
+    Seeds = [{ProcN,rand:uniform(9999)} || ProcN <- lists:seq(1,NumOfProcs)],
     Parent = self(),
     Pids = [my_spawn_link(fun()-> worker(Seed,InitF,ExecF,FiniF,Laps,Parent,NumOfProcs) end)
 	    || Seed <- Seeds],
@@ -5806,7 +5802,7 @@ run_workers_do(InitF,ExecF,FiniF,Laps, Exclude) ->
 	    
 worker({ProcN,Seed}, InitF, ExecF, FiniF, Laps, Parent, NumOfProcs) ->
     io:format("smp worker ~p, seed=~p~n",[self(),Seed]),
-    random:seed(Seed,Seed,Seed),
+    rand:seed(exsplus, {Seed,Seed,Seed}),
     State1 = InitF([ProcN, NumOfProcs]),
     State2 = worker_loop(Laps, ExecF, State1),
     Result = FiniF(State2),
diff --git a/lib/stdlib/test/ets_tough_SUITE.erl b/lib/stdlib/test/ets_tough_SUITE.erl
index c6f24fc..8a7f2b1 100644
--- a/lib/stdlib/test/ets_tough_SUITE.erl
+++ b/lib/stdlib/test/ets_tough_SUITE.erl
@@ -92,7 +92,7 @@ ex1_sub(Config) ->
     ok.
 
 prep(Config) ->
-    random:seed(),
+    rand:seed(exsplus),
     put(dump_ticket,none),
     DumpDir = filename:join(?config(priv_dir,Config), "ets_tough"),
     file:make_dir(DumpDir),
@@ -221,19 +221,19 @@ random_class() ->
     random_element(Classes).
 
 random_key() ->
-    random:uniform(8).
+    rand:uniform(8).
 
 random_value() ->
-    case random:uniform(5) of
+    case rand:uniform(5) of
 	1 -> ok;
 	2 -> {data,random_key()};
 	3 -> {foo,bar,random_class()};
-	4 -> random:uniform(1000);
+	4 -> rand:uniform(1000);
 	5 -> {recursive,random_value()}
     end.
 
 random_element(T) ->
-    I = random:uniform(tuple_size(T)),
+    I = rand:uniform(tuple_size(T)),
     element(I,T).
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index 01b798f..c39ff84 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -318,7 +318,7 @@ same_lists(Expected0, Actual0, BaseDir) ->
 
 mkfiles([H|T], Dir) ->
     Name = filename:join(Dir, H),
-    Garbage = [31+random:uniform(95) || _ <- lists:seq(1, random:uniform(1024))],
+    Garbage = [31+rand:uniform(95) || _ <- lists:seq(1, rand:uniform(1024))],
     file:write_file(Name, Garbage),
     [Name|mkfiles(T, Dir)];
 mkfiles([], _) -> [].
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index a0f7fd2..bd68c93 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -1677,8 +1677,7 @@ check_stab(L, U, S, US, SS) ->
 %%% Element 3 in the tuple is the position of the tuple in the list.
 
 biglist(N) ->
-    {A, B, C} = get_seed(),
-    random:seed(A, B, C),
+    rand:seed(exsplus),
     biglist(N, []).
 
 biglist(0, L) ->
@@ -1694,8 +1693,7 @@ biglist(N, L) ->
 %%% No sequence number.
 
 ubiglist(N) ->
-    {A, B, C} = get_seed(),
-    random:seed(A, B, C),
+    rand:seed(exsplus),
     ubiglist(N, []).
 
 ubiglist(0, L) ->
@@ -1719,8 +1717,7 @@ urandom_tuple(N, I) ->
 %%% sequence number.
 
 bigfunlist(N) ->
-    {A, B, C} = get_seed(),
-    random:seed(A, B, C),
+    rand:seed(exsplus),
     bigfunlist_1(N).
 
 bigfunlist_1(N) when N < 30000 -> % Now (R8) max 32000 different pids.
@@ -1754,21 +1751,13 @@ make_fun(Pid) ->
 fun_pid(Fun) ->
     erlang:fun_info(Fun, pid).
 
-get_seed() ->
-    case random:seed() of
-	undefined ->
-	    erlang:timestamp();
-	Tuple ->
-	    Tuple
-    end.
-
 random_tuple(N, Seq) ->
     R1 = randint(N),
     R2 = randint(N),
     {R1, R2, Seq}.
 
 randint(N) ->
-    trunc(random:uniform() * N).
+    trunc(rand:uniform() * N).
 
 %% The first "duplicate" is kept.
 no_dups([]) ->
@@ -1830,8 +1819,7 @@ sort_loop_1(Pid) ->
     end.
 
 sloop(N) ->
-    {A, B, C} = get_seed(),
-    random:seed(A, B, C),
+    rand:seed(exsplus),
     sloop(N, #state{}).
 
 sloop(N, S) ->
diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl
index c965a8b..5165ac3 100644
--- a/lib/stdlib/test/queue_SUITE.erl
+++ b/lib/stdlib/test/queue_SUITE.erl
@@ -470,7 +470,7 @@ oops(suite) ->
 oops(Config) when is_list(Config) ->
     ?line N = 3142,
     ?line Optab = optab(),
-    ?line Seed0 = random:seed0(),
+    ?line Seed0 = rand:seed(exsplus, {1,2,4}),
     ?line {Is,Seed} = random_list(N, tuple_size(Optab), Seed0, []),
     ?line io:format("~p ", [Is]),
     ?line QA = queue:new(),
@@ -562,20 +562,20 @@ args([], _, Seed, R) ->
 args([q|Ts], [Q|Qs]=Qss, Seed, R) ->
     args(Ts, if Qs =:= [] -> Qss; true -> Qs end, Seed, [Q|R]);
 args([l|Ts], Qs, Seed0, R) ->
-    {N,Seed1} = random:uniform_s(17, Seed0),
+    {N,Seed1} = rand:uniform_s(17, Seed0),
     {L,Seed} = random_list(N, 4711, Seed1, []),
     args(Ts, Qs, Seed, [L|R]);
 args([t|Ts], Qs, Seed0, R) ->
-    {T,Seed} = random:uniform_s(4711, Seed0),
+    {T,Seed} = rand:uniform_s(4711, Seed0),
     args(Ts, Qs, Seed, [T|R]);
 args([n|Ts], Qs, Seed0, R) ->
-    {N,Seed} = random:uniform_s(17, Seed0),
+    {N,Seed} = rand:uniform_s(17, Seed0),
     args(Ts, Qs, Seed, [N|R]).
 
 random_list(0, _, Seed, R) ->
     {R,Seed};
 random_list(N, M, Seed0, R) ->
-    {X,Seed} = random:uniform_s(M, Seed0),
+    {X,Seed} = rand:uniform_s(M, Seed0),
     random_list(N-1, M, Seed, [X|R]).
 
 call(Func, As) ->
diff --git a/lib/stdlib/test/random_iolist.erl b/lib/stdlib/test/random_iolist.erl
index 9a0f034..6da7da0 100644
--- a/lib/stdlib/test/random_iolist.erl
+++ b/lib/stdlib/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/lib/stdlib/test/random_unicode_list.erl b/lib/stdlib/test/random_unicode_list.erl
index ecafe42..3bc86a8 100644
--- a/lib/stdlib/test/random_unicode_list.erl
+++ b/lib/stdlib/test/random_unicode_list.erl
@@ -85,7 +85,7 @@ int_to_utf32_little(I) ->
 id(I) -> I.
 
 random_char() ->
-     case random:uniform(16#10FFFF+1) - 1 of
+     case rand:uniform(16#10FFFF+1) - 1 of
 	 X when X >= 16#D800,
 	  X =< 16#DFFF ->
 	     random_char();
@@ -116,13 +116,13 @@ random_binary(N,Enc) ->
 					   int_to(Enc,X)
 				   end,
 				   L)),
-    case {random:uniform(3),size(B)} of
+    case {rand:uniform(3),size(B)} of
 	{2,M} when M > 1 ->
 	    B2 = id(<<1:3,B/binary,1:5>>),
 	    <<_:3,C:M/binary,_:5>> = B2,
 	    C;
 	{3,M} when M > 1 ->
-	    X = random:uniform(M+1)-1,
+	    X = rand:uniform(M+1)-1,
 	    <<B1:X/binary,B2/binary>> = B,
 	    [B1,B2];
 	_ ->
@@ -132,7 +132,7 @@ random_list(N) ->
     random_list(N,[]).
 
 front() ->
-    case random:uniform(10) of
+    case rand:uniform(10) of
 	10 ->
 	    false;
 	_ ->
@@ -140,7 +140,7 @@ front() ->
     end.
 
 any_type() ->
-    case random:uniform(10) of
+    case rand:uniform(10) of
 	1 ->
 	    list;
 	2 ->
@@ -152,7 +152,7 @@ any_type() ->
     end.
 
 tail_type() ->
-    case random:uniform(5) of
+    case rand:uniform(5) of
 	1 ->
 	    list;
 	2 ->
@@ -165,9 +165,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_unicode_list(0,Acc,_Enc) ->
@@ -214,7 +214,7 @@ random_unicode_list(N,Enc) ->
     
 
 standard_seed() ->
-    random:seed(1201,855653,380975).
+    rand:seed(exsplus, {1201,855653,380975}).
 
 do_comp(List,F1,F2) ->
     X = F1(List),
diff --git a/lib/stdlib/test/run_pcre_tests.erl b/lib/stdlib/test/run_pcre_tests.erl
index 1fdc777..b7d1df3 100644
--- a/lib/stdlib/test/run_pcre_tests.erl
+++ b/lib/stdlib/test/run_pcre_tests.erl
@@ -1083,7 +1083,7 @@ dumponesplit(F,{RE,Line,O,TS}) ->
 %% Generate replacement tests from indatafile, 
 %% you will need perl on the machine
 gen_repl_test(OneFile) ->
-    random:seed(1219,687731,62804),
+    rand:seed(exsplus, {1219,687731,62804}),
     {ok,Bin} = file:read_file(OneFile),
     Lines = splitfile(0,Bin,1),
     Structured = stru(Lines),
@@ -1237,15 +1237,15 @@ btr(_) ->
 
 
 ranchar() ->
-    case random:uniform(10) of
+    case rand:uniform(10) of
 	9 -> $&;
         10 -> <<"\\1">>;		 
 	N when N < 5 ->
-	    random:uniform($Z-$A)+$A-1;
+	    rand:uniform($Z-$A)+$A-1;
 	M when M < 9 ->
-	    random:uniform($z-$a)+$a-1
+	    rand:uniform($z-$a)+$a-1
     end.
 
 ranstring() ->
-    iolist_to_binary([ranchar() || _ <- lists:duplicate(random:uniform(20),0) ]).
+    iolist_to_binary([ranchar() || _ <- lists:duplicate(rand:uniform(20),0) ]).
 
diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl
index ead64ff..6796676 100644
--- a/lib/stdlib/test/select_SUITE.erl
+++ b/lib/stdlib/test/select_SUITE.erl
@@ -212,11 +212,10 @@ init_random(Config) ->
 	       {ok,[X]} ->
 		   X;
 	       _ ->
-		   {A,B,C} = erlang:timestamp(),
-		   random:seed(A,B,C),
-		   get(random_seed)
+		   rand:seed(exsplus),
+		   rand:export_seed()
 	   end,
-    put(random_seed,Seed),
+    rand:seed(Seed),
     {ok, F} = file:open(filename:join([WriteDir, "last_random_seed2.txt"]), 
 			[write]),
     io:format(F,"~p. ~n",[Seed]),
@@ -224,11 +223,11 @@ init_random(Config) ->
     ok.
 
 create_random_key(N,Type) ->
-    gen_key(random:uniform(N),Type).
+    gen_key(rand:uniform(N),Type).
 
 create_pb_key(N,list) ->
-    X = random:uniform(N),
-    case random:uniform(4) of
+    X = rand:uniform(N),
+    case rand:uniform(4) of
 	3 -> {[X, X+1, '_'], fun([Z,Z1,P1]) ->  
 				      [Z,Z1,P1] =:= [X,X+1,P1] end};
 	2 -> {[X, '_', '_'], fun([Z,P1,P2]) ->  [Z,P1,P2] =:= [X,P1,P2] end};
@@ -237,14 +236,14 @@ create_pb_key(N,list) ->
 	_ -> {[X, '$1', '$2'], fun([Z,P1,P2]) ->  [Z,P1,P2] =:= [X,P1,P2] end}
     end;
 create_pb_key(N, tuple) ->
-    X = random:uniform(N),
-    case random:uniform(2) of
+    X = rand:uniform(N),
+    case rand:uniform(2) of
 	1 -> {{X, X+1, '$1'},fun({Z,Z1,P1}) ->  {Z,Z1,P1} =:= {X,X+1,P1} end};
 	_ -> {{X, '$1', '$2'},fun({Z,P1,P2}) ->  {Z,P1,P2} =:= {X,P1,P2} end}
     end;
 create_pb_key(N, complex) ->
-    X = random:uniform(N),
-    case random:uniform(2) of
+    X = rand:uniform(N),
+    case rand:uniform(2) of
 	1 -> {{[X, X+1], '$1'}, fun({[Z,Z1],P1}) ->  
 					{[Z,Z1],P1} =:= {[X,X+1],P1} end};
 	_ -> {{[X, '$1'], '$2'},fun({[Z,P1],P2}) -> 
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index 972a812..e7fc559 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -107,9 +107,9 @@ add_element_del([H|T], M, S, Del, []) ->
     add_element_del(T, M, M(add_element, {H,S}), Del, [H]);
 add_element_del([H|T], M, S0, Del, Inserted) ->
     S1 = M(add_element, {H,S0}),
-    case random:uniform(3) of
+    case rand:uniform(3) of
 	1 ->
-	    OldEl = lists:nth(random:uniform(length(Inserted)), Inserted),
+	    OldEl = lists:nth(rand:uniform(length(Inserted)), Inserted),
 	    S = M(del_element, {OldEl,S1}),
 	    add_element_del(T, M, S, [OldEl|Del], [H|Inserted]);
 	_ ->
@@ -438,7 +438,7 @@ iterate_1(M) ->
     M(empty, []).
 
 iterate_2(M) ->
-    random:seed(1, 2, 42),
+    rand:seed(exsplus, {1,2,42}),
     iter_set(M, 1000).
 
 iter_set(_M, 0) ->
@@ -447,7 +447,7 @@ iter_set(M, N) ->
     L = [I || I <- lists:seq(1, N)],
     T = M(from_list, L),
     L = lists:reverse(iterate_set(M, T)),
-    R = random:uniform(N),
+    R = rand:uniform(N),
     S = lists:reverse(iterate_set(M, R, T)),
     S = [E || E <- L, E >= R],
     iter_set(M, N-1).
@@ -481,7 +481,7 @@ sets_mods() ->
 
 test_all(Tester) ->
     Res = [begin
-	       random:seed(1, 2, 42),
+	       rand:seed(exsplus, {1,2,42}),
 	       S = Tester(M),
 	       {M(size, S),lists:sort(M(to_list, S))}
 	   end || M <- sets_mods()],
@@ -492,7 +492,7 @@ test_all([{Low,High}|T], Tester) ->
 test_all([Sz|T], Tester) when is_integer(Sz) ->
     List = rnd_list(Sz),
     Res = [begin
-		     random:seed(19, 2, Sz),
+		     rand:seed(exsplus, {19,2,Sz}),
 		     S = Tester(List, M),
 		     {M(size, S),lists:sort(M(to_list, S))}
 		 end || M <- sets_mods()],
@@ -512,10 +512,10 @@ rnd_list(Sz) ->
     rnd_list_1(Sz, []).
     
 atomic_rnd_term() ->
-    case random:uniform(3) of
-	1 -> list_to_atom(integer_to_list($\s+random:uniform(94))++"rnd");
-	2 -> random:uniform();
-	3 -> random:uniform(50)-37
+    case rand:uniform(3) of
+	1 -> list_to_atom(integer_to_list($\s+rand:uniform(94))++"rnd");
+	2 -> rand:uniform();
+	3 -> rand:uniform(50)-37
     end.
 
 rnd_list_1(0, Acc) -> Acc;
@@ -543,7 +543,7 @@ remove_some(List0, P) ->
     end.
 
 remove_some([H|T], P, Acc) ->
-    case random:uniform() of
+    case rand:uniform() of
 	F when F < P ->				%Remove.
 	    remove_some(T, P, Acc);
 	_ ->
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index 057d82f..10dcfad 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -80,8 +80,6 @@ report_result(Error) -> ?line test_server:fail(Error).
 big_test(N) ->
     C = start_collect(),
     system_time(), system_time(), system_time(),
-    random:seed(erlang:timestamp()),
-    random:uniform(100),random:uniform(100),random:uniform(100),
 
     big_loop(C, N, []),
 
@@ -127,17 +125,17 @@ big_loop(C, N, Pids) ->
     after 0 ->
 
 	    %% maybe start an interval timer test
-	    Pids1 = maybe_start_i_test(Pids, C, random:uniform(4)),
+	    Pids1 = maybe_start_i_test(Pids, C, rand:uniform(4)),
 	    
 	    %% start 1-4 "after" tests
-	    Pids2 = start_after_test(Pids1, C, random:uniform(4)),
+	    Pids2 = start_after_test(Pids1, C, rand:uniform(4)),
 	    %%Pids2=Pids1,
 
 	    %% wait a little while
-	    timer:sleep(random:uniform(200)*3),
+	    timer:sleep(rand:uniform(200)*3),
 
 	    %% spawn zero, one or two nrev to get some load ;-/
-	    Pids3 = start_nrev(Pids2, random:uniform(100)),
+	    Pids3 = start_nrev(Pids2, rand:uniform(100)),
 	    
 	    big_loop(C, N-1, Pids3)
     end.
@@ -148,20 +146,20 @@ start_nrev(Pids, N) when N < 25 ->
 start_nrev(Pids, N) when N < 75 ->
     [spawn_link(timer_SUITE, do_nrev, [1])|Pids];
 start_nrev(Pids, _N) ->
-    NrevPid1 = spawn_link(timer_SUITE, do_nrev, [random:uniform(1000)*10]),
+    NrevPid1 = spawn_link(timer_SUITE, do_nrev, [rand:uniform(1000)*10]),
     NrevPid2 = spawn_link(timer_SUITE, do_nrev, [1]),
     [NrevPid1,NrevPid2|Pids].
     
 
 start_after_test(Pids, C, 1) ->
-    TO1 = random:uniform(100)*47,
+    TO1 = rand:uniform(100)*47,
     [s_a_t(C, TO1)|Pids];
 start_after_test(Pids, C, 2) ->
-    TO1 = random:uniform(100)*47,
-    TO2 = TO1 div random:uniform(3) + 101,
+    TO1 = rand:uniform(100)*47,
+    TO2 = TO1 div rand:uniform(3) + 101,
     [s_a_t(C, TO1),s_a_t(C, TO2)|Pids];
 start_after_test(Pids, C, N) ->
-    TO1 = random:uniform(100)*47,
+    TO1 = rand:uniform(100)*47,
     start_after_test([s_a_t(C, TO1)|Pids], C, N-1).
 
 s_a_t(C, TimeOut) ->
@@ -187,8 +185,8 @@ a_t(C, TimeOut) ->
 
 maybe_start_i_test(Pids, C, 1) ->
     %% ok do it
-    TOI = random:uniform(53)*49,
-    CountI = random:uniform(10) + 3,                      % at least 4 times
+    TOI = rand:uniform(53)*49,
+    CountI = rand:uniform(10) + 3,		% at least 4 times
     [spawn_link(timer_SUITE, i_t, [C, TOI, CountI])|Pids];
 maybe_start_i_test(Pids, _C, _) ->
     Pids.
-- 
2.1.4

openSUSE Build Service is sponsored by