New Random Number Generator

Mark4Flies at aol.com Mark4Flies at aol.com
Mon Jul 29 12:25:09 UTC 2002


The information about the different way that Squeak and C handle unsigned 
long integers in shift operations was interesting but amazingly it made no 
difference in the outcome. Here is the revised class definition.

-Mark

'From Squeak3.0 of 4 February 2001 [latest update: #3545] on 29 July 2002 at 
8:24:39 am'!
Random subclass: #MTRandom
    instanceVariableNames: 'mt mti '
    classVariableNames: 'LowerMask M MatrixA N TemperingMaskB TemperingMaskC 
UpperMask '
    poolDictionaries: ''
    category: 'Kernel-Numbers'!

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:07'!
mask: aWord1 and: aWord2 
    "Perform bit logic and maintain unsigned four-word 32-bit integers"
    ^ ((aWord1 bitAnd: UpperMask)
        bitOr: (aWord2 bitAnd: LowerMask))! !

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:06'!
temperingShiftL: anInteger
    "Second of four Mersenne Twister shifts"

    ^ (anInteger >> 18 bitAnd: 2r11111111111111)! !

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:06'!
temperingShiftS: anInteger
    "Second of four Mersenne Twister shifts"

    ^ (anInteger << 7 bitAnd: 16rFFFFFFFF)! !

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:06'!
temperingShiftT: anInteger
    "Second of four Mersenne Twister shifts"

    ^ (anInteger << 15 bitAnd: 16rFFFFFFFF)! !

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:06'!
temperingShiftU: anInteger
    "First of four Mersenne Twister shifts"

    ^ (anInteger >> 11 bitAnd: 2r111111111111111111111)! !

!MTRandom methodsFor: 'supporting' stamp: 'mwb 7/29/2002 08:07'!
xor: aWord1 and: aWord2 
    ^ ((aWord1
        bitXor: (aWord2 >> 1 bitAnd: 2097151))
        bitXor: ((WordArray with: 0 with: MatrixA)
                at: (aWord2 bitAnd: 1)
                        + 1))! !


!MTRandom methodsFor: 'initialization' stamp: 'mwb 7/29/2002 08:08'!
initialize
    "Set up space for seeds, then fill them in"
    | s |
    mt _ WordArray new: N.
    mti _ N + 1.
    [s _ Time millisecondClockValue.
    s = 0] whileTrue.
    self sgenrand: s! !


!MTRandom methodsFor: 'accessing' stamp: 'mwb 7/27/2002 09:47'!
next
    "Answer a random Float in the interval [0 to 1)."

    ^ (self nextValue / 16rFFFFFFFF) asFloat! !

!MTRandom methodsFor: 'accessing' stamp: 'mwb 7/26/2002 17:37'!
nextInt: anInteger
    "Answer a random integer in the interval [1, anInteger]."

    ^ (self next * anInteger) truncated + 1! !


!MTRandom methodsFor: 'private' stamp: 'mwb 7/27/2002 11:16'!
genrand
    | y |

    self mti >= N
        ifTrue: [self mti = (N + 1) ifTrue: [self sgenrand: 4357].
            1
                to: N - M
                do: [:kk | 
                    y _ self mask: (self mt at: kk) and: (self mt at: kk + 
1).
                    self mt
                        at: kk
                        put: (self xor: (self mt at: kk + M) and: y)].
            N - M + 1
                to: N - 1
                do: [:kk | 
                    y _ self mask: (self mt at: kk) and: (self mt at: kk + 
1).
                    self mt
                        at: kk
                        put: (self xor: (self mt at: kk + (M - N)) and: y)].
            y _ self mask: (self mt at: N) and: (self mt at: 1).
            self mt
                at: N
                put: (self xor: (self mt at: M) and: y).
            mti _ 1].
    y _ self mt at: mti.
    mti _ mti + 1.
    y _ (y bitXor: (self temperingShiftU: y)) bitAnd: 16rFFFFFFFF.
    y _ ((y bitXor: (self temperingShiftS: y)) bitAnd: TemperingMaskB) 
bitAnd: 16rFFFFFFFF.
    y _ ((y bitXor: (self temperingShiftT: y)) bitAnd: TemperingMaskC) 
bitAnd: 16rFFFFFFFF.
    y _ (y bitXor: (self temperingShiftL: y)) bitAnd: 16rFFFFFFFF.
    ^ y! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/26/2002 11:38'!
mt
    ^ mt! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/26/2002 16:23'!
mti
    ^ mti! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/26/2002 16:23'!
mti: anInteger
    mti _ anInteger! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/26/2002 20:56'!
nextValue
    "This method generates random instances of Integer.     The algorithm
    is described in detail by M. Matsumoto and T. Nishimura
    in 'Mersenne Twister: A 623-dimensionally equidistributed uniform
    pseudorandom number generator', ACM Trans. on Modeling and
    Computer Simulation Vol. 8, No. 1, January pp.3-30 1998."

    ^ self genrand! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/29/2002 07:45'!
seed: anInteger 
    seed _ anInteger.
    self sgenrand: anInteger! !

!MTRandom methodsFor: 'private' stamp: 'mwb 7/26/2002 17:36'!
sgenrand: anInteger 
    mt
        at: 1
        put: (anInteger bitAnd: 16rFFFFFFFF).
    2
        to: N
        do: [:i | self mt
            at: i
            put: (69069 * (self mt at: i - 1) bitAnd: 16rFFFFFFFF)].
    self mti: N
    ! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

MTRandom class
    instanceVariableNames: ''!

!MTRandom class methodsFor: 'instance creation' stamp: 'mwb 7/26/2002 10:54'!
new
    "Create new instance of MTRandom"

    ^ super new initialize! !


!MTRandom class methodsFor: 'class initialization' stamp: 'mwb 7/27/2002 
11:23'!
initialize
    " MTRandom initialize "

    "Set period parameters"
    N _ 624.
    M _ 397.
    MatrixA _ 16r9908B0DF.
    LowerMask _ 16r7FFFFFFF.
    UpperMask _ 16r80000000.

    "Set tempering parameters"
    TemperingMaskB _ 16r9D2C5680.
    TemperingMaskC _ 16rEFC60000! !


MTRandom initialize!



More information about the Squeak-dev mailing list