File 8211-lib-dialyzer-test-replace-random-uniform-1-by-rand-u.patch of Package erlang

From 7bf573cb7047321c6b0f169f77e7cb6640235157 Mon Sep 17 00:00:00 2001
From: Ariel Otilibili <otilibil@eurecom.fr>
Date: Thu, 12 Dec 2024 12:37:06 +0100
Subject: [PATCH] lib/dialyzer/test: replace random:uniform/1 by rand:uniform/1

```
$ git grep -Pn 'random:uniform' | \
    awk -F: '/lib\/dialyzer\/test/{ \
    cmd = sprintf("sed -i -e '%ds/random:uniform/rand:uniform/' %s\n", $2,$1); \
    system(cmd); \
    close(cmd)
    }'
```

Link: https://www.erlang.org/doc/deprecations.html#functions-deprecated-in-otp-19
Signed-off-by: Ariel Otilibili <otilibil@eurecom.fr>
---
 .../test/indent_SUITE_data/src/map_galore.erl | 20 +++++++++----------
 .../indent_SUITE_data/src/simple/is_rec.erl   |  2 +-
 .../test/map_SUITE_data/src/map_galore.erl    | 20 +++++++++----------
 .../opaque_SUITE_data/src/simple/is_rec.erl   |  2 +-
 .../options2_SUITE_data/src/kernel/global.erl |  2 +-
 .../r9c_SUITE_data/src/asn1/asn1ct_value.erl  |  2 +-
 .../r9c_SUITE_data/src/mnesia/mnesia_lib.erl  |  4 ++--
 .../test/small_SUITE_data/src/false_false.erl |  2 +-
 8 files changed, 27 insertions(+), 27 deletions(-)

diff --git a/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
index 46c4c77d98..7b80ef8d66 100644
--- a/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
+++ b/lib/dialyzer/test/indent_SUITE_data/src/map_galore.erl
@@ -1527,7 +1527,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,
@@ -1558,7 +1558,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
@@ -1649,9 +1649,9 @@ cmp_others(T1, T2, _) ->
 
 map_gen(Pairs, Size) ->
     {_,L} = lists:foldl(fun(_, {Keys, Acc}) ->
-				KI = random:uniform(tuple_size(Keys)),
+				KI = rand:uniform(tuple_size(Keys)),
 				K = element(KI,Keys),
-				KV = element(random:uniform(tuple_size(K)), K),
+				KV = element(rand:uniform(tuple_size(K)), K),
 				{erlang:delete_element(KI,Keys), [KV | Acc]}
 			end,
 			{Pairs, []},
@@ -1691,15 +1691,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),
@@ -1713,7 +1713,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),
@@ -1722,7 +1722,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/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl b/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
index b906431b44..e3179d8380 100644
--- a/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
+++ b/lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl
@@ -27,7 +27,7 @@ ri14() ->
 -spec '1-3'() -> '1-3-t'().
 
 '1-3'() ->
-    random:uniform(3).
+    rand:uniform(3).
 
 
 -spec 'Atom'() -> atom().
diff --git a/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl b/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
index dfb0e18b3a..3c01c29d44 100644
--- a/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
+++ b/lib/dialyzer/test/map_SUITE_data/src/map_galore.erl
@@ -1527,7 +1527,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,
@@ -1558,7 +1558,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
@@ -1649,9 +1649,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, []},
@@ -1691,15 +1691,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),
@@ -1713,7 +1713,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),
@@ -1722,7 +1722,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/lib/dialyzer/test/opaque_SUITE_data/src/simple/is_rec.erl b/lib/dialyzer/test/opaque_SUITE_data/src/simple/is_rec.erl
index b906431b44..e3179d8380 100644
--- a/lib/dialyzer/test/opaque_SUITE_data/src/simple/is_rec.erl
+++ b/lib/dialyzer/test/opaque_SUITE_data/src/simple/is_rec.erl
@@ -27,7 +27,7 @@ ri14() ->
 -spec '1-3'() -> '1-3-t'().
 
 '1-3'() ->
-    random:uniform(3).
+    rand:uniform(3).
 
 
 -spec 'Atom'() -> atom().
diff --git a/lib/dialyzer/test/options2_SUITE_data/src/kernel/global.erl b/lib/dialyzer/test/options2_SUITE_data/src/kernel/global.erl
index 302adaae96..2cb740254f 100644
--- a/lib/dialyzer/test/options2_SUITE_data/src/kernel/global.erl
+++ b/lib/dialyzer/test/options2_SUITE_data/src/kernel/global.erl
@@ -1868,7 +1868,7 @@ random_sleep(Times) ->
     Tmax = if Times > 5 -> 8000;
 	      true -> ((1 bsl Times) * 1000) div 8
 	   end,
-    T = random:uniform(Tmax),
+    T = rand:uniform(Tmax),
     ?P({random_sleep, node(), self(), Times, T}),
     receive after T -> ok end.
 
diff --git a/lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_value.erl b/lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_value.erl
index 81968b9f92..e3a378dc4f 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_value.erl
+++ b/lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_value.erl
@@ -259,7 +259,7 @@ c_string(C,Default) ->
 random(Upper) ->
     {A1,A2,A3} = erlang:now(),
     random:seed(A1,A2,A3),
-    random:uniform(Upper).
+    rand:uniform(Upper).
 
 size_random(C) ->
     case get_constraint(C,'SizeConstraint') of
diff --git a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
index 9e0cdac2dc..40b9111eea 100644
--- a/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
+++ b/lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl
@@ -840,11 +840,11 @@ random_time(Retries, _Counter0) ->
 	undefined ->
 	    {X, Y, Z} = erlang:now(), %% time()
 	    random:seed(X, Y, Z),
-	    Time = Dup + random:uniform(MaxIntv),
+	    Time = Dup + rand:uniform(MaxIntv),
 	    %%	    dbg_out("---random_test rs ~w max ~w val ~w---~n", [Retries, MaxIntv, Time]),
 	    Time;
 	_ ->
-	    Time = Dup + random:uniform(MaxIntv),
+	    Time = Dup + rand:uniform(MaxIntv),
 	    %%	    dbg_out("---random_test rs ~w max ~w val ~w---~n", [Retries, MaxIntv, Time]),
 	    Time
     end.
diff --git a/lib/dialyzer/test/small_SUITE_data/src/false_false.erl b/lib/dialyzer/test/small_SUITE_data/src/false_false.erl
index e8efc42868..b72748dc36 100644
--- a/lib/dialyzer/test/small_SUITE_data/src/false_false.erl
+++ b/lib/dialyzer/test/small_SUITE_data/src/false_false.erl
@@ -20,7 +20,7 @@ false_or() ->
   false or false.
 
 wips() ->
-  case new_execute_cmd(random:uniform(2)) of
+  case new_execute_cmd(rand:uniform(2)) of
     ok -> mostly_good;
     _ -> and_here_we_are
   end.
-- 
2.43.0

openSUSE Build Service is sponsored by