Skip to content

Commit 8916501

Browse files
committed
Use more bits when shuffling
Also, use specified algorithms when measuring.
1 parent 8e8f742 commit 8916501

File tree

2 files changed

+67
-40
lines changed

2 files changed

+67
-40
lines changed

lib/stdlib/src/rand.erl

Lines changed: 34 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -533,6 +533,7 @@ the generator's range:
533533
exs1024_next/1, exs1024_calc/2,
534534
exro928_next_state/4,
535535
exrop_next/1, exrop_next_s/2,
536+
shuffle_new_bits/1,
536537
mwc59_value/1,
537538
get_52/1, normal_kiwi/1]}).
538539

@@ -606,7 +607,7 @@ the generator's range:
606607
-type alg_handler() ::
607608
#{type := alg(),
608609
bits => non_neg_integer(),
609-
weak_low_bits => non_neg_integer(),
610+
weak_low_bits => 0..3,
610611
max => non_neg_integer(), % Deprecated
611612
next :=
612613
fun ((alg_state()) -> {non_neg_integer(), alg_state()}),
@@ -1503,17 +1504,9 @@ and the [`NewState`](`t:state/0`).
15031504
when
15041505
List :: list(),
15051506
State :: state().
1506-
shuffle_s(List, {#{bits:=_, next:=Next} = AlgHandler, R0})
1507+
shuffle_s(List, {AlgHandler, R0})
15071508
when is_list(List) ->
1508-
WeakLowBits = maps:get(weak_low_bits, AlgHandler, 0),
1509-
[P0|S0] = shuffle_init_bitstream(R0, Next, WeakLowBits),
1510-
{ShuffledList, _P1, [R1|_]=_S1} = shuffle_r(List, [], P0, S0),
1511-
{ShuffledList, {AlgHandler, R1}};
1512-
shuffle_s(List, {#{max:=_, next:=Next} = AlgHandler, R0})
1513-
when is_list(List) ->
1514-
%% Old spec - assume 2 weak low bits
1515-
WeakLowBits = 2,
1516-
[P0|S0] = shuffle_init_bitstream(R0, Next, WeakLowBits),
1509+
[P0|S0] = shuffle_init_bitstream(R0, AlgHandler),
15171510
{ShuffledList, _P1, [R1|_]=_S1} = shuffle_r(List, [], P0, S0),
15181511
{ShuffledList, {AlgHandler, R1}}.
15191512

@@ -1607,9 +1600,9 @@ shuffle_r([], Acc0, P0, S0, Zero, One, Two, Three) ->
16071600
{Acc3, P3, S3} = shuffle_r(Two, Acc2, P2, S2),
16081601
shuffle_r(Three, Acc3, P3, S3);
16091602
shuffle_r([X | L], Acc, P0, S, Zero, One, Two, Three)
1610-
when is_integer(P0), 3 < P0, P0 < 1 bsl 57 ->
1603+
when is_integer(P0), ?BIT(2) =< P0, P0 =< ?MASK(59) ->
16111604
P1 = P0 bsr 2,
1612-
case P0 band 3 of
1605+
case ?MASK(2, P0) of
16131606
0 -> shuffle_r(L, Acc, P1, S, [X | Zero], One, Two, Three);
16141607
1 -> shuffle_r(L, Acc, P1, S, Zero, [X | One], Two, Three);
16151608
2 -> shuffle_r(L, Acc, P1, S, Zero, One, [X | Two], Three);
@@ -1621,8 +1614,8 @@ shuffle_r([_ | _] = L, Acc, _P, S0, Zero, One, Two, Three) ->
16211614

16221615
%% Permute 2 elements
16231616
shuffle_r_2(X, Acc, P, S, Y)
1624-
when is_integer(P), 1 < P, P < 1 bsl 57 ->
1625-
{case P band 1 of
1617+
when is_integer(P), ?BIT(1) =< P, P =< ?MASK(59) ->
1618+
{case ?MASK(1, P) of
16261619
0 -> [Y, X | Acc];
16271620
1 -> [X, Y | Acc]
16281621
end, P bsr 1, S};
@@ -1636,9 +1629,9 @@ shuffle_r_2(X, Acc, _P, S0, Y) ->
16361629
%% to reject and retry, which on average is 3 * 4/3
16371630
%% (infinite sum of (1/4)^k) = 4 bits per permutation
16381631
shuffle_r_3(X, Acc, P0, S, Y, Z)
1639-
when is_integer(P0), 7 < P0, P0 < 1 bsl 57 ->
1632+
when is_integer(P0), ?BIT(3) =< P0, P0 =< ?MASK(59) ->
16401633
P1 = P0 bsr 3,
1641-
case P0 band 7 of
1634+
case ?MASK(3, P0) of
16421635
0 -> {[Z, Y, X | Acc], P1, S};
16431636
1 -> {[Y, Z, X | Acc], P1, S};
16441637
2 -> {[Z, X, Y | Acc], P1, S};
@@ -1652,24 +1645,37 @@ shuffle_r_3(X, Acc, _P, S0, Y, Z) ->
16521645
[P|S1] = shuffle_new_bits(S0),
16531646
shuffle_r_3(X, Acc, P, S1, Y, Z).
16541647

1655-
-dialyzer({no_improper_lists, shuffle_init_bitstream/3}).
16561648
%%
1657-
shuffle_init_bitstream(R, Next, WeakLowBits) ->
1649+
shuffle_init_bitstream(R, #{bits:=Bits, next:=Next} = AlgHandler) ->
1650+
Mask = ?MASK(Bits),
1651+
Shift = maps:get(weak_low_bits, AlgHandler, 0),
1652+
shuffle_init_bitstream(R, Next, Shift, Mask);
1653+
shuffle_init_bitstream(R, #{max:=Mask, next:=Next}) ->
1654+
%% Old spec - assume 2 weak low bits
1655+
Shift = 2,
1656+
shuffle_init_bitstream(R, Next, Shift, Mask).
1657+
%%
1658+
-dialyzer({no_improper_lists, shuffle_init_bitstream/4}).
1659+
shuffle_init_bitstream(R, Next, Shift, Mask0) ->
1660+
Mask = ?MASK(58, Mask0), % Limit the mask to avoid bignum
16581661
P = 1, % Marker for out of random bits
1659-
W = {Next,WeakLowBits}, % Generator
1662+
W = {Next,Shift,Mask}, % Generator
16601663
S = [R|W], % Generator state
16611664
[P|S]. % Bit cash and state
16621665

16631666
-dialyzer({no_improper_lists, shuffle_new_bits/1}).
16641667
%%
1665-
shuffle_new_bits([R0|{Next,WeakLowBits}=W]) ->
1666-
{V, R1} = Next(R0),
1667-
%% Setting the top bit M here provides the marker
1668-
%% for when we are out of random bits: P =:= 1
1669-
M = 1 bsl 56,
1670-
P = ((V bsr WeakLowBits) band (M-1)) bor M,
1671-
S = [R1|W],
1672-
[P|S].
1668+
shuffle_new_bits([R0|{Next,Shift,Mask}=W])
1669+
when is_integer(Shift), 0 =< Shift, Shift =< 3,
1670+
is_integer(Mask), 0 < Mask, Mask =< ?MASK(58) ->
1671+
case Next(R0) of
1672+
{V, R1} when is_integer(V) ->
1673+
%% Setting the top bit here provides the marker
1674+
%% for when we are out of random bits: P =:= 1
1675+
P = ((V bsr Shift) band Mask) bor (Mask + 1),
1676+
S = [R1|W],
1677+
[P|S]
1678+
end.
16731679

16741680
%% =====================================================================
16751681
%% Internal functions

lib/stdlib/test/rand_SUITE.erl

Lines changed: 33 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -55,8 +55,6 @@ suite() ->
5555
all() ->
5656
[seed, interval_int, interval_float,
5757
bytes_count,
58-
shuffle_elements, shuffle_reference,
59-
basic_stats_shuffle, measure_shuffle,
6058
api_eq,
6159
mwc59_api,
6260
exsp_next_api, exsp_jump_api,
@@ -68,13 +66,17 @@ all() ->
6866
plugin, measure,
6967
{group, reference_jump},
7068
short_jump,
69+
{group, shuffle},
7170
doctests
7271
].
7372

7473
groups() ->
7574
[{basic_stats, [parallel],
7675
[basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_bytes,
7776
basic_stats_standard_normal]},
77+
{shuffle, [],
78+
[shuffle_elements, shuffle_reference,
79+
basic_stats_shuffle, measure_shuffle]},
7880
{distr_stats, [parallel],
7981
[stats_standard_normal_box_muller,
8082
stats_standard_normal_box_muller_2,
@@ -89,6 +91,9 @@ group(distr_stats) ->
8991
%% valgrind needs a lot of time
9092
[{timetrap,{minutes,10}}];
9193
group(reference_jump) ->
94+
%% valgrind needs a lot of time
95+
[{timetrap,{minutes,10}}];
96+
group(shuffle) ->
9297
%% valgrind needs a lot of time
9398
[{timetrap,{minutes,10}}].
9499

@@ -414,10 +419,13 @@ bytes_count(Config) when is_list(Config) ->
414419
%% Check that shuffle doesn't loose or duplicate elements
415420

416421
shuffle_elements(Config) when is_list(Config) ->
417-
M = 20,
418-
SortedList = lists:seq(0, (1 bsl M) - 1),
422+
SortedList = lists:seq(1, 1010_101),
419423
State = rand:seed(default),
420-
case lists:sort(rand:shuffle(SortedList)) of
424+
{ShuffledList, NewState} = rand:shuffle_s(SortedList, State),
425+
true = ShuffledList =:= rand:shuffle(SortedList),
426+
NewSeed = rand:export_seed_s(NewState),
427+
NewSeed = rand:export_seed(),
428+
case lists:sort(ShuffledList) of
421429
SortedList -> ok;
422430
_ ->
423431
error({mismatch, State})
@@ -428,13 +436,26 @@ shuffle_elements(Config) when is_list(Config) ->
428436
%% Check that shuffle is repeatable
429437

430438
shuffle_reference(Config) when is_list(Config) ->
431-
M = 20,
439+
M = 20,
440+
List = lists:seq(0, (1 bsl M) - 1),
432441
Seed = {1,2,3},
433-
MD5 = <<56,202,188,237,192,69,132,182,227,54,33,68,45,74,208,89>>,
434-
%%
435-
SortedList = lists:seq(0, (1 bsl M) - 1),
436-
S = rand:seed_s(default, Seed),
437-
{ShuffledList, NewS} = rand:shuffle_s(SortedList, S),
442+
Ref =
443+
[{exsss,
444+
<<124,54,150,191,198,136,245,103,157,213,96,6,210,103,134,107>>},
445+
{exro928ss,
446+
<<160,170,223,95,44,254,192,107,145,180,236,235,102,110,72,131>>},
447+
{exrop,
448+
<<175,236,222,199,129,54,205,86,81,38,92,219,66,71,30,69>>},
449+
{exs1024s,
450+
<<148,169,164,28,198,202,108,206,123,68,189,26,116,210,82,116>>},
451+
{exsp,
452+
<<63,163,228,59,249,88,205,251,225,174,227,65,144,130,169,191>>}],
453+
[shuffle_reference(M, List, Seed, Alg, MD5) || {Alg, MD5} <- Ref],
454+
ok.
455+
456+
shuffle_reference(M, List, Seed, Alg, MD5) ->
457+
S = rand:seed_s(Alg, Seed),
458+
{ShuffledList, NewS} = rand:shuffle_s(List, S),
438459
Data = mk_iolist(ShuffledList, M),
439460
case erlang:md5(Data) of
440461
MD5 -> ok;
@@ -517,7 +538,7 @@ measure_shuffle(Config) when is_list(Config) ->
517538
end;
518539
measure_shuffle(Effort) when is_integer(Effort) ->
519540
Algs =
520-
[default, exs1024 |
541+
[exsss, exs1024 |
521542
case crypto_support() of
522543
ok -> [crypto];
523544
_ -> []

0 commit comments

Comments
 (0)