[squeak-dev] The Trunk: Kernel-ul.907.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Feb 26 21:05:54 UTC 2015


Levente Uzonyi uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-ul.907.mcz

==================== Summary ====================

Name: Kernel-ul.907
Author: ul
Time: 26 February 2015, 9:26:09.288 pm
UUID: a94084a6-3f89-4708-8e60-b7978f1b3501
Ancestors: Kernel-ul.906

Removed the old random number generator implementation from Random.

=============== Diff against Kernel-ul.906 ===============

Item was changed:
  ----- Method: LargePositiveInteger>>atRandom: (in category 'truncation and round off') -----
+ atRandom: aRandom
+ 	"Answer a random integer from 1 to self picked from aRandom."
- atRandom: aGenerator
- 	"Answer a random integer from 1 to self picked from aGenerator."
  
+ 	^aRandom nextLargeInt: self!
- 	| chunkByteLength chunkBitLength chunkCount chunkMax bigRandomInteger |
- 	chunkByteLength := 3.
- 	chunkBitLength := chunkByteLength * 8.
- 	chunkCount :=
- 		self highBitOfMagnitude + chunkBitLength - 1 // chunkBitLength "self would fit in that many chunks..."
- 		 + 2. "and two more chunks (48 bits) so as to have a pretty fair distribution"
- 	chunkMax := 1<<chunkBitLength-1.
- 	
- 	"fill a big random integer by chunks of 3 bytes (24 bits)"
- 	bigRandomInteger := self class new: chunkCount*chunkByteLength neg: false.
- 	0 to: chunkCount*chunkByteLength - 1 by: chunkByteLength do: [:byteOffset | 
- 		| chunk |
- 		chunk := (aGenerator nextInt: chunkMax) - 1.
- 		1 to: chunkByteLength do: [:byteIndex |
- 			bigRandomInteger digitAt: byteOffset + byteIndex put: (chunk digitAt: byteIndex)]].
- 
- 	^self * bigRandomInteger >> (chunkCount * chunkBitLength) + 1!

Item was changed:
  Object subclass: #Random
+ 	instanceVariableNames: 'states index seed'
- 	instanceVariableNames: 'seed states index'
  	classVariableNames: 'A M MTa MTbShifted MTcShifted MTl MTlowerMask MTm MTn MTs MTt MTu MTupperMask MTw MTwFloatMultiplier MTwordMask Q R'
  	poolDictionaries: ''
  	category: 'Kernel-Numbers'!
  
+ !Random commentStamp: 'ul 2/20/2015 09:44' prior: 0!
+ I implement the 32-bit version of the Mersenne Twister PRNG, using 30-bit arithmetic, based on http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/ARTICLES/mt.pdf . The parameters of the generator are stored in class variables prefixed with MT.
- !Random commentStamp: 'nice 3/24/2010 07:38' prior: 0!
- This Random Number Generator graciously contributed by David N. Smith.  It is an adaptation of the Park-Miller RNG which uses Floats to avoid the need for LargeInteger arithmetic.
  
+ Instance Variables
+ 	states:	<Array>
+ 	index: <Integer>
+ 
+ index
+ 	- the index of the state, which should be used to generate the next random integer value
+ 
+ states
+ 	- an Array holding the internal state of the generator
+ 
+ ---
+ 
  If you just want a quick random integer, use:
  		10 atRandom
  Every integer interval can give a random number:
  		(6 to: 12) atRandom
  SequenceableCollections can give randomly selected elements:
  		'pick one of these letters randomly' atRandom
  SequenceableCollections also respond to shuffled, as in:
  		($A to: $Z) shuffled
  
  The correct way to use class Random is to store one in an instance or class variable:
  		myGenerator := Random new.
  Then use it every time you need another number between 0.0 and 1.0 (excluding)
  		myGenerator next
  You can also generate a positive integer
  		myGenerator nextInt: 10!

Item was changed:
  ----- Method: Random class>>initialize (in category 'class initialization') -----
  initialize
  	"30-bit MT521 parameters. generated with a modified version of dcmt with ID=1. http://www.math.sci.hiroshima-u.ac.jp/~m-mat/MT/DC/dc.html"
  
  	"Base parameters"
  	"MTp := 521. Not used directly."
  	MTw := 30.
  	MTm := 9.
  	MTa := 16r3235DEE2.
  	"MTb := 16r39BB2B00. Not used directly."
  	"MTc := 16r3EFD0000. Not used directly."
  	MTl := -18.
  	MTu := -12.
  	MTs := 7.
  	MTt := 15.
  	"Calculated parameters"
  	MTn := 18.
  	"MTr := 19. Not used directly."
  	MTupperMask := 16r3FF80000.
  	MTlowerMask := 16r7FFFF.
  	MTwordMask := 16r3FFFFFFF.
  	MTbShifted := 7566934.
  	MTcShifted := 32250.
+ 	MTwFloatMultiplier := 8388608!
- 	MTwFloatMultiplier := 8388608.
- 	self allInstancesDo: [ :each | each instVarNamed: #seed put: nil; seed: nil ]!

Item was changed:
  ----- Method: Random>>initialize (in category 'initialization') -----
  initialize
  	
+ 	self seed: nil!
- 	self seed: seed!

Item was removed:
- ----- Method: Random>>initializeStates (in category 'private') -----
- initializeStates
- 	"Initialize the states array with the seed."
- 
- 	states := Array new: MTn.
- 	1 to: MTn do: [ :i | 
- 		states at: i put: (MTwordMask bitAnd: seed).
- 		seed := 16rFFFFFFFF bitAnd: (16r6C078965 * (seed bitXor: seed //  16r40000000 "bitShift: -30") + i) ]!

Item was added:
+ ----- Method: Random>>initializeStatesWith: (in category 'private') -----
+ initializeStatesWith: anInteger
+ 	"Initialize the states array with the seed."
+ 
+ 	| seed |
+ 	states := Array new: MTn.
+ 	seed := anInteger.
+ 	1 to: MTn do: [ :i | 
+ 		states at: i put: (MTwordMask bitAnd: seed).
+ 		seed := 16rFFFFFFFF bitAnd: (16r6C078965 * (seed bitXor: seed //  16r40000000 "bitShift: -30") + i) ]!

Item was changed:
  ----- Method: Random>>next (in category 'accessing') -----
  next
  	"Answer a random 53-bit Float from the [0, 1) interval. The implementation assumes that the MTw parameter is between 27 and 53."
  	
- 	seed isFloat ifTrue: [
- 		"Answer a random Float in the interval [0 to 1)."
- 		^ (seed := self nextValue) - 1.0 / M ].
  	^self nextValue asFloat * MTwFloatMultiplier + (self nextValue bitAnd: MTwFloatMultiplier - 1) / 9.007199254740992e15 "(1 << 53) asFloat"!

Item was changed:
  ----- Method: Random>>nextInt: (in category 'accessing') -----
  nextInt: anInteger
  	"Answer a random integer value from the interval [1, anInteger]"
  
  	| bucketSize retriesLeft |
  	anInteger strictlyPositive ifFalse: [ self error: 'Range must be positive' ].
- 	seed isFloat ifTrue: [
- 		" Answer a random integer in the interval [1, anInteger]. anInteger should be less than 16r80000000. "
- 		"avoid Float arithmetic in #next to work with LargeInts"
- 		^ ((seed := self nextValue) asInteger * anInteger // M asInteger) + 1 ].
  	(anInteger isLarge 
  		or: [ anInteger > MTwordMask "In case SmallIntegers have more than MTw-bits, but the generator hasn't been updated accordingly." ]) 
  		ifTrue: [ ^self nextLargeInt: anInteger ].
- 
  	"Split the MTw-bit(currently 30-bit) integer range up to the equal sized buckets. Generate an MTw-bit random number, and see which bucket it's in. If it doesn't fit in any bucket, then try again."
  	bucketSize := MTwordMask // anInteger. "The optimal bucket size would be MTwordMask + 1 // anInteger, but calculating it would involve LargeInteger arithmetic. The MTwordMask // anInteger expression is suboptimal only when anInteger is a power of two. These cases are rare, and the effect is negligible for small values. We could handle these cases separately, but testing if anInteger is a power of two costs more in general."
  	retriesLeft := 10. "Based on measurements with various seeds, 10 retries is about optimal for the worst case, when anInteger = MTwordMask // 2 + 1."
  	[ (retriesLeft := retriesLeft - 1) >= 0 ] whileTrue: [
  		| bucket |
  		bucket := self nextValue // bucketSize.
  		bucket < anInteger ifTrue: [ ^bucket + 1 ] ].
  	"Fall back to the floating point method, which is slower, but when we get here, then we've already spent enough resources on trying to generate the number. Using this fallback also ensures that the method doesn't run for indefinitely long."
  	^(self next * anInteger) truncated + 1!

Item was changed:
  ----- Method: Random>>nextValue (in category 'private') -----
  nextValue
  	"Answer an MTw-bit random integer between 0 and wordMask, and increment the index."
  
  	| y |
- 	seed isFloat ifTrue: [
- 		"This method generates random instances of Integer in the interval 1 to 16r7FFFFFFF. This method does NOT update the seed; repeated sends answer the same value.
- 		The algorithm is described in detail in 'Random Number Generators: 
- 		Good Ones Are Hard to Find' by Stephen K. Park and Keith W. Miller 
- 		(Comm. Asso. Comp. Mach., 31(10):1192--1201, 1988)."
- 		| lo hi aLoRHi |
- 		hi := seed quo: Q.
- 		lo := seed - (Q * hi).  " = seed rem: q"  
- 		aLoRHi := (A * lo) - (R * hi).
- 		aLoRHi > 0.0 ifTrue: [ ^aLoRHi ].
- 		^aLoRHi + M ].
  	y := states at: index.
  	(index := index + 1) > MTn ifTrue: [ self generateStates ].
  	y := y bitXor: (y bitShift: MTu).
  	y := ((y bitAnd: MTbShifted) bitShift: MTs) bitXor: y.
  	y := ((y bitAnd: MTcShifted) bitShift: MTt) bitXor: y.
  	y := (y bitShift: MTl) bitXor: y.
  	^y!

Item was removed:
- ----- Method: Random>>seed (in category 'private') -----
- seed
- 	^ seed!

Item was changed:
  ----- Method: Random>>seed: (in category 'initialization') -----
  seed: anIntegerOrNil
  	" Use the given integer as seed, or generate one if it's nil. "
  
  	| newSeed |
  	newSeed := anIntegerOrNil ifNil: [
  		| now |
  		now := Time primUTCMicrosecondClock.
  		now = 0 ifTrue: [ now := Time millisecondClockValue ].
  		(now bitShift: 28) bitXor: self hash hashMultiply ].
+ 	(newSeed between: 0 and: 16rFFFFFFFF) ifFalse: [ 
+ 		newSeed := self hashSeed: newSeed ].
- 	seed isFloat ifTrue: [
- 		(newSeed between: 0 and: 16r7FFFFFFF)
- 			ifTrue: [ seed := newSeed asFloat ]
- 			ifFalse: [ seed := ((self hashSeed: newSeed) bitXor: 16r7FFFFFFF) asFloat ].
- 		^self ].
- 	(newSeed between: 0 and: 16rFFFFFFFF)
- 		ifTrue: [ seed := newSeed ]
- 		ifFalse: [ seed := self hashSeed: newSeed ].
  	self 
+ 		initializeStatesWith: newSeed;
- 		initializeStates;
  		generateStates!



More information about the Squeak-dev mailing list