@@ -431,7 +431,7 @@ the generator's range:
431431
432432[](){: #modulo-method }
433433- **Modulo**
434- To generate a number `V` in the range `0 .. Range-1`:
434+ To generate a number `V` in the range `0 .. Range-1`:
435435
436436 > Generate a number `X`.
437437 > Use `V = X rem Range` as your value.
@@ -447,12 +447,12 @@ the generator's range:
447447 have a bias. Example:
448448
449449 Say the generator generates a byte, that is, the generator range
450- is `0 .. 255`, and the desired range is `0 .. 99` (`Range = 100`).
450+ is `0 .. 255`, and the desired range is `0 .. 99` (`Range = 100`).
451451 Then there are 3 generator outputs that produce the value `0`,
452- these are; `0`, `100` and `200`.
452+ these are `0`, `100` and `200`.
453453 But there are only 2 generator outputs that produce the value `99`,
454- which are; `99` and `199`. So the probability for a value `V` in `0 .. 55`
455- is 3/2 times the probability for the other values `56 .. 99`.
454+ which are `99` and `199`. So the probability for a value `V` in `0 .. 55`
455+ is 3/2 times the probability for the other values `56 .. 99`.
456456
457457 If `Range` is much smaller than the generator range, then this bias
458458 gets hard to detect. The rule of thumb is that if `Range` is smaller
@@ -468,8 +468,8 @@ the generator's range:
468468
469469[](){: #truncated-multiplication-method }
470470- **Truncated multiplication**
471- To generate a number `V` in the range `0 .. Range-1`, when you have
472- a generator with a power of 2 range (`0 .. 2^Bits-1`):
471+ To generate a number `V` in the range `0 .. Range-1`, when you have
472+ a generator with a power of 2 range (`0 .. 2^Bits-1`):
473473
474474 > Generate a number `X`.
475475 > Use `V = X * Range bsr Bits` as your value.
@@ -486,8 +486,8 @@ the generator's range:
486486
487487[](){: #shift-or-mask-method }
488488- **Shift or mask**
489- To generate a number in a power of 2 range (`0 .. 2^RBits-1`),
490- when you have a generator with a power of 2 range (`0 .. 2^Bits`):
489+ To generate a number in a power of 2 range (`0 .. 2^RBits-1`),
490+ when you have a generator with a power of 2 range (`0 .. 2^Bits`):
491491
492492 > Generate a number `X`.
493493 > Use `V = X band ((1 bsl RBits)-1)` or `V = X bsr (Bits-RBits)`
@@ -525,7 +525,7 @@ will not create a bignum.
525525
526526The recommended way to generate a floating point number
527527(IEEE 745 Double, that has got a 53-bit mantissa) in the range
528- `0 .. 1`, that is `0.0 =< V < 1.0` is to generate a 53-bit number `X`
528+ `0 .. 1`, that is `0.0 =< V < 1.0` is to generate a 53-bit number `X`
529529and then use `V = X * (1.0/((1 bsl 53)))` as your value.
530530This will create a value of the form N*2^-53 with equal probability
531531for every possible N for the range.
@@ -595,9 +595,9 @@ for every possible N for the range.
595595% % Types
596596% % =====================================================================
597597
598- -doc " `0 .. (2^64 - 1)`" .
598+ -doc " `0 .. (2^64 - 1)`" .
599599-type uint64 () :: 0 ..? MASK (64 ).
600- -doc " `0 .. (2^58 - 1)`" .
600+ -doc " `0 .. (2^58 - 1)`" .
601601-type uint58 () :: 0 ..? MASK (58 ).
602602
603603% % This depends on the algorithm handler function
@@ -613,7 +613,7 @@ for every possible N for the range.
613613% %
614614% % The 'bits' field indicates how many bits the integer
615615% % returned from 'next' has got, i.e 'next' shall return
616- % % an random integer in the range 0.. (2^Bits - 1).
616+ % % an random integer in the range 0 .. (2^Bits - 1).
617617% % At least 55 bits is required for the floating point
618618% % producing fallbacks, but 56 bits would be more future proof.
619619% %
@@ -784,17 +784,17 @@ To be used with `seed/1`.
7847841> S = rand:seed(exsss, 4711).
785785%% Export the (initial) state
7867862> E = rand:export_seed().
787- %% Generate an integer N in the interval 1 .. 1000000
788- 3> rand:uniform(1000000 ).
787+ %% Generate an integer N in the interval 1 .. 1_000_000
788+ 3> rand:uniform(1_000_000 ).
789789334013
790790%% Start over with E that may have been stored
791791%% in ETS, on file, etc...
7927924> rand:seed(E).
793- 5> rand:uniform(1000000 ).
793+ 5> rand:uniform(1_000_000 ).
794794334013
795795%% Within the same node this works just as well
7967966> rand:seed(S).
797- 7> rand:uniform(1000000 ).
797+ 7> rand:uniform(1_000_000 ).
798798334013
799799```
800800""" .
@@ -819,20 +819,20 @@ To be used with `seed/1`.
8198191> S0 = rand:seed_s(exsss, 4711).
820820%% Export the (initial) state
8218212> E = rand:export_seed_s(S0).
822- %% Generate an integer N in the interval 1 .. 1000000
823- 3> {N, S1} = rand:uniform_s(1000000 , S0).
822+ %% Generate an integer N in the interval 1 .. 1_000_000
823+ 3> {N, S1} = rand:uniform_s(1_000_000 , S0).
8248244> N.
825825334013
826826%% Start over with E that may have been stored
827827%% in ETS, on file, etc...
8288285> S2 = rand:seed_s(E).
829829%% S2 is equivalent to S0
830- 6> {N, S3} = rand:uniform_s(1000000 , S2).
830+ 6> {N, S3} = rand:uniform_s(1_000_000 , S2).
831831%% S3 is equivalent to S1
8328327> N.
833833334013
834834%% Within the same node this works just as well
835- 6> {N, S4} = rand:uniform_s(1000000 , S0).
835+ 6> {N, S4} = rand:uniform_s(1_000_000 , S0).
836836%% S4 is equivalent to S1
8378377> N.
838838334013
@@ -1048,8 +1048,8 @@ the process dictionary. Returns the generated number `X`.
10481048```erlang
10491049%% Initialize a predictable PRNG sequence
105010501> rand:seed(exsss, 4711).
1051- %% Generate an integer in the interval 1 .. 1000000
1052- 2> rand:uniform(1000000 ).
1051+ %% Generate an integer in the interval 1 .. 1_000_000
1052+ 2> rand:uniform(1_000_000 ).
10531053334013
10541054```
10551055""" .
@@ -1132,8 +1132,8 @@ Returns the number `X` and the updated `NewState`.
11321132```erlang
11331133%% Initialize a predictable PRNG sequence
113411341> S0 = rand:seed_s(exsss, 4711).
1135- %% Generate an integer N in the interval 1 .. 1000000
1136- 2> {N, S1} = rand:uniform_s(1000000 , S0).
1135+ %% Generate an integer N in the interval 1 .. 1_000_000
1136+ 2> {N, S1} = rand:uniform_s(1_000_000 , S0).
113711373> N.
11381138334013
11391139```
@@ -1594,8 +1594,8 @@ no jump function implemented for the [`State`](`t:state/0`)'s algorithm.
15941594%% Initialize a predictable PRNG sequence
159515951> Sa0 = rand:seed_s(exsss, 4711).
159615962> Sb0 = rand:jump(Sa0).
1597- %% Sa and Sb can now be used for surely
1598- %% non-overlapping PRNG sequences
1597+ %% Sa and Sb can now be used for non-overlapping PRNG
1598+ %% sequences since they are separated by 2^64 iterations
159915993> {BytesA, Sa1} = rand:bytes_s(10, Sa0).
160016004> {BytesB, Sb1} = rand:bytes_s(10, Sb0).
160116015> BytesA.
@@ -1635,8 +1635,8 @@ the process dictionary. Returns the [`NewState`](`t:state/0`).
16351635 rand:jump(),
16361636 Parent ! {self(), rand:bytes(10)}
16371637 end).
1638- %% Parent and Pid now produce surely
1639- %% non-overlapping PRNG sequences
1638+ %% Parent and Pid now produce non-overlapping PRNG
1639+ %% sequences since they are separated by 2^64 iterations
164016404> rand:bytes(10).
16411641<<72,232,227,197,77,149,79,57,9,136>>
164216425> receive {Pid, Bytes} -> Bytes end.
@@ -1909,7 +1909,7 @@ shuffle_s(List, {AlgHandler, R0})
19091909% % Also, it is faster to do a 4-way split by 2 bits instead of,
19101910% % as described above, a 2-way split by 1 bit.
19111911
1912- % % Leaf cases - random permutations for 0.. 3 elements
1912+ % % Leaf cases - random permutations for 0 .. 3 elements
19131913shuffle_r ([], Acc , P , S ) ->
19141914 {Acc , P , S };
19151915shuffle_r ([X ], Acc , P , S ) ->
@@ -2439,7 +2439,7 @@ exs1024_next({[H], RL}) ->
24392439% % This is the jump function for the exs1024 generator, equivalent
24402440% % to 2^512 calls to next(); it can be used to generate 2^512
24412441% % non-overlapping subsequences for parallel computations.
2442- % % Note: the jump function takes ~2000 times of the execution time of
2442+ % % Note: the jump function takes ~ 2 000 times of the execution time of
24432443% % next/1.
24442444
24452445% % Jump constant here split into 58 bits for speed
@@ -2910,7 +2910,7 @@ dummy_seed({A1, A2, A3}) ->
29102910-define (MWC59_XS2 , 27 ).
29112911
29122912-doc """
2913- `1 .. (16#1ffb072 bsl 29) - 2`
2913+ `1 .. (16#1ffb072 bsl 29) - 2`
29142914""" .
29152915-type mwc59_state () :: 1 ..? MWC59_P - 1 .
29162916
@@ -2983,7 +2983,7 @@ is 60% of the time for the default algorithm generating a `t:float/0`.
298329837714
29842984%% Generate an integer 0 .. 999 with not noticeable bias
298529852> CX2 = rand:mwc59(CX1).
2986- 3> CX2 rem 1000 .
2986+ 3> CX2 rem 1_000 .
2987298786
29882988```
29892989""" .
@@ -3019,7 +3019,7 @@ When using this scrambler it is in general better to use the high bits of the
30193019value than the low. The lowest 8 bits are of good quality and are passed
30203020right through from the base generator. They are combined with the next 8
30213021in the xorshift making the low 16 good quality, but in the range
3022- 16 .. 31 bits there are weaker bits that should not become high bits
3022+ 16 .. 31 bits there are weaker bits that should not become high bits
30233023of the generated values.
30243024
30253025Therefore it is in general safer to shift out low bits.
@@ -3040,7 +3040,7 @@ that is: `(Range*V) bsr 32`, which is much faster than using `rem`.
304030402935831586
30413041%% Generate an integer 0 .. 999 with not noticeable bias
304230422> CX2 = rand:mwc59(CX1).
3043- 3> (rand:mwc59_value32(CX2) * 1000 ) bsr 32.
3043+ 3> (rand:mwc59_value32(CX2) * 1_000 ) bsr 32.
30443044540
30453045```
30463046""" .
@@ -3065,10 +3065,10 @@ the low. See the recipes in section [Niche algorithms](#niche-algorithms).
30653065
30663066For a non power of 2 range less than about 20 bits (to not get
30673067too much bias and to avoid bignums) truncated multiplication can be used,
3068- which is much faster than using `rem`. Example for range 1' 000' 000;
3068+ which is much faster than using `rem`. Example for range 1 000 000;
30693069the range is 20 bits, we use 39 bits from the generator,
30703070adding up to 59 bits, which is not a bignum (on a 64-bit VM ):
3071- `(1000_000 * (V bsr (59-39))) bsr 39`.
3071+ `(1_000_000 * (V bsr (59-39))) bsr 39`.
30723072
30733073#### _Shell Example_
30743074
@@ -3079,13 +3079,13 @@ adding up to 59 bits, which is not a bignum (on a 64-bit VM ):
307930792> CX1 = rand:mwc59(CX0).
308030803> rand:mwc59_value(CX1) bsr (59-48).
30813081247563052677727
3082- %% Generate an integer 0 .. 1'000'000 with not noticeable bias
3082+ %% Generate an integer 0 .. 1_000_000 with not noticeable bias
308330834> CX2 = rand:mwc59(CX1).
3084- 5> ((rand:mwc59_value(CX2) bsr (59-39)) * 1000_000 ) bsr 39.
3084+ 5> ((rand:mwc59_value(CX2) bsr (59-39)) * 1_000_000 ) bsr 39.
30853085144457
3086- %% Generate an integer 0 .. 1'000'000'000 with not noticeable bias
3086+ %% Generate an integer 0 .. 1_000_000_000 with not noticeable bias
308730874> CX3 = rand:mwc59(CX2).
3088- 5> rand:mwc59_value(CX3) rem 1000_000_000 .
3088+ 5> rand:mwc59_value(CX3) rem 1_000_000_000 .
30893089949193925
30903090```
30913091""" .
@@ -3138,7 +3138,7 @@ just like [`seed_s(atom())`](`seed_s/1`).
313831381> CX0 = rand:mwc59_seed().
31393139%% Generate an integer 0 .. 999 with not noticeable bias
314031402> CX1 = rand:mwc59(CX0).
3141- 3> CX1 rem 1000 .
3141+ 3> CX1 rem 1_000 .
31423142```
31433143""" .
31443144-doc (#{group => <<" Niche algorithms API" >>,since => <<" OTP 25.0" >>}).
0 commit comments