Skip to content

Commit 36ec985

Browse files
committed
Revert "Try dedicated shuffle_exsss"
This reverts commit 5dd78a1.
1 parent 5dd78a1 commit 36ec985

File tree

1 file changed

+0
-83
lines changed

1 file changed

+0
-83
lines changed

lib/stdlib/src/rand.erl

Lines changed: 0 additions & 83 deletions
Original file line numberDiff line numberDiff line change
@@ -1832,9 +1832,6 @@ and the [`NewState`](`t:state/0`).
18321832
when
18331833
List :: list(),
18341834
State :: state().
1835-
shuffle_s(List, {#{type:=exsss} = AlgHandler, S}) ->
1836-
{ShuffledList, _P1, NewS} = shuffle_s_exsss(List, S),
1837-
{ShuffledList, {AlgHandler, NewS}};
18381835
shuffle_s(List, {#{type:=mwc59} = AlgHandler, CX0}) ->
18391836
{ShuffledList, _P1, CX1} = shuffle_s_mwc59(List, CX0),
18401837
{ShuffledList, {AlgHandler, CX1}};
@@ -2387,86 +2384,6 @@ exsplus_jump(S, [AS0|AS1], J, N) ->
23872384
exsplus_jump(NS, [AS0|AS1], J bsr 1, N-1)
23882385
end.
23892386

2390-
%% -------
2391-
2392-
shuffle_s_exsss(List, S) ->
2393-
shuffle_exsss_r(List, [], 1, S).
2394-
2395-
%% Leaf cases - random permutations for 0..3 elements
2396-
shuffle_exsss_r([], Acc, P, S) ->
2397-
{Acc, P, S};
2398-
shuffle_exsss_r([X], Acc, P, S) ->
2399-
{[X | Acc], P, S};
2400-
shuffle_exsss_r([X, Y], Acc, P, S) ->
2401-
shuffle_exsss_r_2(X, Acc, P, S, Y);
2402-
shuffle_exsss_r([X, Y, Z], Acc, P, S) ->
2403-
shuffle_exsss_r_3(X, Acc, P, S, Y, Z);
2404-
%% General case - split and recursive shuffle
2405-
shuffle_exsss_r([_, _, _ | _] = List, Acc, P, S) ->
2406-
%% P and S is bitstream cache and state
2407-
shuffle_exsss_r(List, Acc, P, S, [], [], [], []).
2408-
%%
2409-
%% Split L into 4 random subsets
2410-
%%
2411-
shuffle_exsss_r([], Acc0, P0, S0, Zero, One, Two, Three) ->
2412-
%% Split done, recursively shuffle the splitted lists onto Acc
2413-
{Acc1, P1, S1} = shuffle_exsss_r(Zero, Acc0, P0, S0),
2414-
{Acc2, P2, S2} = shuffle_exsss_r(One, Acc1, P1, S1),
2415-
{Acc3, P3, S3} = shuffle_exsss_r(Two, Acc2, P2, S2),
2416-
shuffle_exsss_r(Three, Acc3, P3, S3);
2417-
shuffle_exsss_r([X | L], Acc, P0, S, Zero, One, Two, Three)
2418-
when is_integer(P0), 3 < P0, P0 =< ?MASK(59) ->
2419-
P1 = P0 bsr 2,
2420-
case P0 band 3 of
2421-
0 -> shuffle_exsss_r(L, Acc, P1, S, [X | Zero], One, Two, Three);
2422-
1 -> shuffle_exsss_r(L, Acc, P1, S, Zero, [X | One], Two, Three);
2423-
2 -> shuffle_exsss_r(L, Acc, P1, S, Zero, One, [X | Two], Three);
2424-
3 -> shuffle_exsss_r(L, Acc, P1, S, Zero, One, Two, [X | Three])
2425-
end;
2426-
shuffle_exsss_r([_ | _] = L, Acc, _P, [S1|S0], Zero, One, Two, Three) ->
2427-
S0_1 = ?MASK(58, S0),
2428-
S1_1 = ?exs_next(S0_1, S1, Tmp1),
2429-
P = ?scramble_starstar(S0_1, Tmp2, Tmp3) bor ?BIT(58),
2430-
shuffle_exsss_r(L, Acc, P, [S0_1|S1_1], Zero, One, Two, Three).
2431-
2432-
%% Permute 2 elements
2433-
shuffle_exsss_r_2(X, Acc, P, S, Y)
2434-
when is_integer(P), 1 < P, P =< ?MASK(59) ->
2435-
{case P band 1 of
2436-
0 -> [Y, X | Acc];
2437-
1 -> [X, Y | Acc]
2438-
end, P bsr 1, S};
2439-
shuffle_exsss_r_2(X, Acc, _P, [S1|S0], Y) ->
2440-
S0_1 = ?MASK(58, S0),
2441-
S1_1 = ?exs_next(S0_1, S1, Tmp1),
2442-
P = ?scramble_starstar(S0_1, Tmp2, Tmp3) bor ?BIT(58),
2443-
shuffle_exsss_r_2(X, Acc, P, [S0_1|S1_1], Y).
2444-
2445-
%% Permute 3 elements
2446-
%%
2447-
%% Uses 3 random bits per iteration with a probability of 1/4
2448-
%% to reject and retry, which on average is 3 * 4/3
2449-
%% (infinite sum of (1/4)^k) = 4 bits per permutation
2450-
shuffle_exsss_r_3(X, Acc, P0, S, Y, Z)
2451-
when is_integer(P0), 7 < P0, P0 =< ?MASK(59) ->
2452-
P1 = P0 bsr 3,
2453-
case P0 band 7 of
2454-
0 -> {[Z, Y, X | Acc], P1, S};
2455-
1 -> {[Y, Z, X | Acc], P1, S};
2456-
2 -> {[Z, X, Y | Acc], P1, S};
2457-
3 -> {[X, Z, Y | Acc], P1, S};
2458-
4 -> {[Y, X, Z | Acc], P1, S};
2459-
5 -> {[X, Y, Z | Acc], P1, S};
2460-
_ -> % Reject and retry
2461-
shuffle_exsss_r_3(X, Acc, P1, S, Y, Z)
2462-
end;
2463-
shuffle_exsss_r_3(X, Acc, _P, [S1|S0], Y, Z) ->
2464-
S0_1 = ?MASK(58, S0),
2465-
S1_1 = ?exs_next(S0_1, S1, Tmp1),
2466-
P = ?scramble_starstar(S0_1, Tmp2, Tmp3) bor ?BIT(58),
2467-
shuffle_exsss_r_3(X, Acc, P, [S0_1|S1_1], Y, Z).
2468-
2469-
24702387
%% =====================================================================
24712388
%% exs1024 PRNG: Xorshift1024*
24722389
%% Algorithm by Sebastiano Vigna

0 commit comments

Comments
 (0)