Random.st
author Claus Gittinger <cg@exept.de>
Tue, 25 Jun 2019 14:28:51 +0200
changeset 5050 44fa8672d102
parent 4640 84130c41071a
child 5069 c96c32f49875
permissions -rw-r--r--
#DOCUMENTATION by cg class: SharedQueue comment/format in: #next #nextWithTimeout:

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

Stream subclass:#Random
	instanceVariableNames:'seed'
	classVariableNames:'RandomSalt SharedGenerator'
	poolDictionaries:''
	category:'Magnitude-Numbers-Random'
!

!Random class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    A facade to the actual RandomGenerator.
    In previous versions, Random was a very bad fallback random generator,
    with an included warning, to not use it.

    Now this old generator was renamed to RandomGNUSmalltalk,
    and the default generator used is the one provided by the much
    better RandomGenerator class.

        Random new next:10   

    [author:]
        Claus Gittinger

    [see also:]
        http://www0.cs.ucl.ac.uk/staff/d.jones/GoodPracticeRNG.pdf
        RandomTT800      - a new random generator
        RandomParkMiller - another new random generator
"
!

examples
"
                                                                        [exBegin]
    |rnd|

    rnd := Random new.
    10 timesRepeat:[
        Transcript showCR:(rnd next)
    ]
                                                                        [exEnd]

    rolling a dice:
                                                                        [exBegin]
    |rnd|

    rnd := Random new.
    10 timesRepeat:[
        Transcript showCR:(rnd nextIntegerBetween:1 and:6)
    ]
                                                                        [exEnd]
"
! !

!Random class methodsFor:'instance creation'!

new
    "return a new random generator.
     Here, this instance creation message is forwarded to the standardGenerator"

    self == Random ifFalse:[^ super new].
    ^ self standard

    "
     Random new
    "
!

random
    "return a new random generator.
     Defined here for compatibility with StreamCipher"

    ^ self standard

    "Created: / 12.11.1999 / 17:52:08 / stefan"
!

seed:seedValue
    "return a new random generator with initial seed.
     Here, this instance creation message is forwarded to the standardGenerator"

    self == Random ifFalse:[^ self basicNew seed:seedValue].
    ^ self standardGeneratorClass basicNew setSeed:seedValue

    "Created: / 26-05-2007 / 21:27:18 / cg"
!

sharedGenerator
    "return a shared random generator."

    SharedGenerator isNil ifTrue:[
        SharedGenerator := self standard.
    ].
    ^ SharedGenerator
!

standard
    "return the 'standard' generator"

    ^ self standardGeneratorClass new
!

standardGeneratorClass
    "return the class used for the 'standard' generator"

    ^ RandomGenerator
! !

!Random class methodsFor:'random numbers'!

next
    "return the next random number in the range 0..1
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    ^ self sharedGenerator next.

    "
     Transcript showCR:(Random next).
     Transcript showCR:(Random next).
     Transcript showCR:(Random next).
     Transcript showCR:(Random next).
    "
!

nextBetween:start and:stop
    "return a random number between start and stop.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    ^ self sharedGenerator nextBetween:start and:stop

    "
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
     Transcript showCR:(Random nextBetween:1 and:100).
    "

    "Modified: 21.8.1997 / 18:08:56 / cg"
    "Created: 21.8.1997 / 18:09:36 / cg"
!

nextBoolean
    "return a boolean random.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    ^ self sharedGenerator nextBoolean.

    "
     Transcript showCR:(Random nextBoolean).
     Transcript showCR:(Random nextBoolean).
     Transcript showCR:(Random nextBoolean).
     Transcript showCR:(Random nextBoolean).
    "

    "Created: 21.8.1997 / 18:08:23 / cg"
!

nextInteger
    "return an integral random number.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    ^ self sharedGenerator nextInteger.

    "
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
     Transcript showCR:(Random nextInteger).
    "

    "Created: 21.8.1997 / 18:08:23 / cg"
!

nextIntegerBetween:start and:stop
    "return an integral random number between start and stop.
     This method behaves like the corresponding instance method,
     but allows generation of random numbers without
     a need for an instance of Random to be kept around.
     This uses a common, shared generator."

    ^ self sharedGenerator nextIntegerBetween:start and:stop

    "
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
     Transcript showCR:(Random nextIntegerBetween:1 and:10).
    "

    "Created: 21.8.1997 / 18:07:00 / cg"
    "Modified: 21.8.1997 / 18:08:56 / cg"
!

nextLettersOrDigits:count
    "get the next count printable letters or digits [0-9A-Za-z]."

    ^ self sharedGenerator nextLettersOrDigits:count

    "
     Transcript showCR:(Random nextLettersOrDigits:10).
     Transcript showCR:(Random nextLettersOrDigits:10).
     Transcript showCR:(Random nextLettersOrDigits:10).
     Transcript showCR:(Random nextLettersOrDigits:10).
    "

    "Created: 21.8.1997 / 18:07:00 / cg"
    "Modified: 21.8.1997 / 18:08:56 / cg"
! !

!Random class methodsFor:'seeding'!

randomSeed
    "return a number useful for seeding.
     This takes the current processor's time, plus the processor's process id,
     plus some value depending on the memory allocation state,
     plus a random salt, and shuffles those bits around.
     The entropy returned should be reasonable enough for a good seed of a good rnd
     generator. However, keep in mind, that it only has a limited number of entropy bits
     (in the order of 32). 
     But it should be much better than what is commonly used in older
     programs (current time) or even a constant."

    |hash|

    RandomSalt isNil ifTrue:[
        RandomSalt := 1.
    ] ifFalse:[
        RandomSalt := RandomSalt + 1.
    ].

    hash := MD5Stream new.
    hash 
        nextPut:RandomSalt;
        nextPut:Time microsecondClockValue; 
        nextPut:OperatingSystem getProcessId; 
        nextPut:(ObjectMemory addressOf:Object new); 
        nextPut:ObjectMemory oldSpaceUsed; 
        nextPut:ObjectMemory newSpaceUsed; 
        nextPut:OperatingSystem getCPUCycleCount. 

    "/ any other cheap sources of entropy?

    "/ I think there is no problem in that MD5 is not a secure hash algo here 
    "/ - the idea is to shuffle the bits around a bit
    "/ (because the numbers above usually have many high bits in common)
    "/ and then condense the bits into a smaller number.
    "/ Any comment from a crypto guy here - I am willing to change this to some other hash, if that makes a problem

    "/ Seeding rnd generators should take some bits from the returned number (i.e. their max. seed size)
    ^ LargeInteger digitBytes:hash hashValue.

    "
     10 timesRepeat:[Transcript showCR:self randomSeed].
     10 timesRepeat:[Transcript showCR:(self randomSeed bitAnd:16rFFFF)].
     self randomSeed bitAnd:16rFFFFFFFF
    "
! !

!Random class methodsFor:'testing'!

bucketTest: randy
    "A quick-and-dirty bucket test. Prints nbuckets values on the Transcript.
     Each should be 'near' the value of ntries. Any run with any value 'far' from ntries
     indicates something is very wrong. Each run generates different values.
     For a slightly better test, try values of nbuckets of 200-1000 or more; 
     go get coffee.
     This is a poor test; see Knuth.   
     Some 'OK' runs:
           1000 1023 998 969 997 1018 1030 1019 1054 985 1003
           1011 987 982 980 982 974 968 1044 976
           1029 1011 1025 1016 997 1019 991 954 968 999 991
           978 1035 995 988 1038 1009 988 993 976
    "

    | nbuckets buckets ntrys slot |

    nbuckets := 20.
    buckets := Array new: nbuckets withAll:0.
    ntrys :=  1000.
    ntrys*nbuckets timesRepeat: [
            slot := (randy next * nbuckets) floor + 1.
            buckets at: slot put: (buckets at: slot) + 1 ].
    Transcript cr.
    1 to: nbuckets do: [ :nb |
            Transcript show: (buckets at: nb) printString, ' ' ]


    "Execute this:  
         self bucketTest: self new
         self bucketTest: RandomGenerator new
    "
!

chiSquareTest   
    " Chi-Squared Test - from R.Sedgewick's 1st ed. of 'Algorithms', 
            o N = number of samples
            o r  = range of random numners is [0,r)      -- condition: N >= 10r.
            o Random number generator 'passes' if chisquare value is very close to r
            o Repeat test several times, since it may be *wrong* 1 out of 10 trials."

    | aGenerator frequencies n range t |

    aGenerator := self new.  "Seeded differently each time (if seeded at all)"
    range := 100.   
    n := 10000.
    frequencies := Array new:range withAll:0.

    1 to: n do: [:i |
        t := ((aGenerator next) * range) truncated + 1.
        frequencies at:t put: ((frequencies at:t) + 1).
    ].
    t := frequencies inject:0 into: [:nextValue :eachFreq |
            nextValue + eachFreq squared
        ].
    ^ ((range * t  / n) - n) asFloat.

    "
     self chiSquareTest 
     RandomGenerator chiSquareTest
    "

   "
    |fail|
    fail := 0.
    10 timesRepeat:[
        |testResult|
        testResult := RandomGenerator chiSquareTest.
        (100 - testResult) abs > 20 ifTrue:[Transcript showCR:testResult. fail := fail + 1].
    ].
    fail > 1 ifTrue:[self error:'test failed'].
    "

    "
      Sedgewick claims each chisquare number should be 100 +- 20. 
      The closer to 100, the better.
    "
! !

!Random methodsFor:'Compatibility-Squeak'!

nextInt:upperBound
    "Answer a random integer in the interval [1, anInteger]."

    (upperBound < 1) ifTrue:[self error:'invalid upper bound'].

    ^ self nextIntegerBetween:1 and:upperBound

    "
     Random new nextInt:10
    "
!

nextIntFrom:lowerBound to:upperBound
    "return a random integer in the given range"

    ^ self nextIntegerBetween:lowerBound and:upperBound

    "
     Random new nextIntFrom:5 to:10
    "
!

seed: anInteger
    self setSeed: anInteger.

    "Created: / 20-07-2013 / 01:52:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!Random methodsFor:'accessing-reading'!

next
    "return the next random number in the range ]0..1["

    self subclassResponsibility.

    "
     |r|
     r := Random new.
     Transcript showCR:r next.
     Transcript showCR:r next.
     Transcript showCR:r next.
     Transcript showCR:r next.
    "

    "Modified: 1.4.1997 / 22:44:46 / cg"
!

next:count
    "return the next count random numbers in the range ]0..1["

    |answerStream
     cnt  "{ Class: SmallInteger }" |

    cnt := count.
    answerStream := self contentsSpecies writeStream:cnt.
    1 to:cnt do:[:index | |next|
        next := self next.
        answerStream nextPut:next.
    ].
    ^ answerStream contents

    "
     (RandomGenerator new) next:10
    "
!

next:count integerBetween:min and:max
    "return the next count random integers in min..max"

    |answerStream
     cnt  "{ Class: SmallInteger }" |

    cnt := count.
    answerStream := self contentsSpecies writeStream:cnt.
    1 to:cnt do:[:index | |next|
        next := self nextIntegerBetween:min and:max.
        answerStream nextPut:next.
    ].
    ^ answerStream contents

    "
     (RandomGenerator new) next:100 integerBetween:0 and:100
    "
!

nextBetween:start and:stop
    "return a random number in the range ]start..stop[.
     claus: the original GNU version has a bug in returning values
     from the interval [start .. stop+1]"

    |rndFloat rnd|

    rndFloat := self next.
    rnd := (rndFloat * (stop - start) asFloat) + start asFloat.
    ^ rnd

    "
     |r|
     r := Random new.
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
     Transcript showCR:(r nextBetween:1 and:10).
    "

    "Modified: / 21.8.1998 / 14:45:27 / cg"
!

nextBoolean
    "return true or false by random"

    ^ self nextInteger bitAnd:16r10.

    "
    |r|
     r := Random new.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
     Transcript showCR:r nextBoolean.
    "

    "
     |r bag|
     r := Random new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextBoolean).
     ].
     Transcript showCR:bag contents
    "

    "Modified: / 22-10-2008 / 15:17:57 / cg"
!

nextByte
    "return the next integral random number byte in the range 0 .. 16rFF"

    ^ self nextInteger bitAnd:16rFF

    "
     |r|
     r := self new.
     Transcript showCR:r nextByte.
     Transcript showCR:r nextByte.
     Transcript showCR:r nextByte.
     Transcript showCR:r nextByte.
    "

    "Modified: 1.4.1997 / 22:42:53 / cg"
!

nextBytes:count
    "return count random bytes (0..16rFF each)"

    ^ (1 to:count) collect:[:i | self nextByte] as:ByteArray

    "
     Transcript showCR:(RandomGenerator new nextBytes:20).  
    "

    "Modified: 1.4.1997 / 22:42:53 / cg"
!

nextBytesNonZero:count
    "return count random bytes, none of which is zero (i.e. 1..16rFF each)"

    |res cnt "{Class: SmallInteger}"|

    cnt := count.
    res := ByteArray uninitializedNew:cnt.

    1 to:cnt do:[:i|
        |nextNonZero|

        [
            (nextNonZero := self nextByte) == 0
        ] whileTrue.
        res at:i put:nextNonZero.
    ].

    ^ res

    "
     Transcript showCR:(Random new nextBytesNonZero:20).
    "

    "Modified: 1.4.1997 / 22:42:53 / cg"
!

nextCharacters:count
    "get the next cnt printable characters.
     We answer printable characters in the ascii range (codepoints 32 - 126)"

    ^ (1 to:count) collect:[:i | Character value:(self nextInteger \\ 94 + 32) ] as:String

    "
      RandomGenerator new nextCharacters:8 
    "
!

nextInteger
    "return the next integral random number,
     in the range 0 .. self maxInteger"

    self subclassResponsibility

    "
     |r|
     r := Random new.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
     Transcript showCR:r nextInteger.
    "

    "Modified: 1.4.1997 / 22:42:53 / cg"
!

nextIntegerBetween:start and:stop
    "return an integral random number in [start..stop] (inclusive)"

    |rnd range bytesNeeded|

    range := stop - start + 1.
    "Fetch at least 2 bytes, otherwise we get some unbalanced distributions for small ranges"
    bytesNeeded := (range highBit + 15) // 8.
    bytesNeeded < 4 ifTrue:[
        rnd := (((self nextByte bitShift:8) + self nextByte) bitShift:8) + self nextByte.
        rnd := rnd \\ range.
    ] ifFalse:[
        rnd := (LargeInteger digitBytes:(self nextBytes:bytesNeeded)) compressed.
        rnd := rnd \\ range.
    ].
    ^ rnd + start

    "shows pair-combination counts

     |r v prev this counts|

     v := TextView new .
     v extent:500@250.
     v list:#('xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx'
              'xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx xxxx').
     v openAndWait.
     counts := (1 to:10) collect:[:row | Array new:10 withAll:0].

     r := self new.
     prev := r nextIntegerBetween:1 and:10.
     10000 timesRepeat:[
         100 timesRepeat:[
            this := r nextIntegerBetween:1 and:10.
            (counts at:this) at:prev put:((counts at:this) at:prev)+1.
         ].
         v list:(counts collect:[:row |
                    '%4d %4d %4d %4d %4d %4d %4d %4d %4d %4d'printf:row ]).
         prev := this.
     ].
    "

    "
     |r|
     r := self new.
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
     Transcript showCR:(r nextIntegerBetween:1 and:10).
    "

    "
     |r|
     r := self new.
     Transcript showCR:(r nextIntegerBetween:1 and:1000000).
     Transcript showCR:(r nextIntegerBetween:1 and:1000000).
     Transcript showCR:(r nextIntegerBetween:1 and:1000000).
     Transcript showCR:(r nextIntegerBetween:1 and:1000000).
    "

    "
     |r bag|
     r := self new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextIntegerBetween:-1 and:1).
     ].
     Transcript showCR:bag sortedCounts.
    "

    "
     |r bag|
     r := self new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextIntegerBetween:1 and:3).
     ].
     Transcript showCR:bag sortedCounts.
     TestCase assert:(bag standardDeviation closeTo:(((3 squared - 1)/12) sqrt)).
    "

    "
     |r bag|
     r := self new.
     bag := Bag new.
     1000000 timesRepeat:[
         bag add:(r nextIntegerBetween:1 and:32).
     ].
     Transcript showCR:bag sortedCounts.
     TestCase assert:(bag standardDeviation closeTo:(((32 squared - 1)/12) sqrt)).
    "

    "
     |r bag|
     r := self new.
     bag := Bag new.
     100000000 timesRepeat:[
         bag add:(r nextIntegerBetween:1 and:400000).
     ].
     Transcript showCR:bag sortedCounts.
     TestCase assert:(bag standardDeviation closeTo:(((400000 squared - 1)/12) sqrt)).
    "

    "
     |r|
     
     r := self new.
     100000000 timesRepeat:[
         self assert:((r nextIntegerBetween:1 and:3) between:1 and:3).
     ].
    "
!

nextLettersOrDigits:count
    "get a random string consisting of count printable letters or digits [0-9A-Za-z]."

    |res cnt "{ Class:SmallInteger }"|

    cnt := count.
    res := String uninitializedNew:cnt.

    1 to:cnt do:[:i|
        self step.
        res 
            at:i 
            put:('1234567890ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz' at:(seed \\ 62 + 1)).
    ].

    ^ res

    "
      Random new nextLettersOrDigits:40 
    "
! !

!Random methodsFor:'blocked methods'!

contents
    "blocked from use - contents makes no sense for random generators"

    self shouldNotImplement
!

nextPut: value
    "blocked from use - it makes no sense for randoms"

    self shouldNotImplement
! !

!Random methodsFor:'initialization'!

initialize
    self setSeed
! !

!Random methodsFor:'private'!

addEntropy:entropyBytes
    "add some entropy - ignored here"

    ^ self
!

seed
    ^ seed
!

setSeed
    "set the initial seed value based on the current time and processId.
     These numbers implement a maximum period generator which passes
     the spectral test for randomness for dimensions 2 3 4 5 6 and
     the product does not overflow  2 raisedTo:29.

     Use both time and processId for seed, to make different processes
     return different Random numbers"

    |newSeed|

    RandomSalt isNil ifTrue:[
        RandomSalt := 1.
    ] ifFalse:[
        RandomSalt := RandomSalt + 1.
    ].
    newSeed := RandomSalt + (Time millisecondClockValue bitXor:OperatingSystem getProcessId).
    self setSeed:newSeed.

    "Modified: / 29-05-2007 / 12:07:37 / cg"
!

setSeed:seedValue
    "set the initial seed and intialize the PRNG parameters."

    self subclassResponsibility.

    "Modified: / 12-11-1999 / 17:50:52 / stefan"
    "Created: / 26-05-2007 / 21:25:10 / cg"
!

step
    "compute the next random integer"

    self subclassResponsibility
! !

!Random methodsFor:'testing'!

atEnd
    "instances of Random can always give more numbers"

    ^ false
!

isReadable
    ^ true
!

isWritable
    "return true, if writing is supported by the receiver.
     Random Generators never are"

    ^ false

    "Created: 1.4.1997 / 22:38:27 / cg"
!

maxInteger
    "the max value returned by self nextInteger"

    self subclassResponsibility
! !

!Random class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !