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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 26 21:03:25 UTC 2015


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

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

Name: Kernel-ul.906
Author: ul
Time: 26 February 2015, 9:22:02.722 pm
UUID: 9fd0ffbc-c774-442a-baa5-5b0e13950856
Ancestors: Kernel-topa.905

Added an implementation of a 30-bit Mersenne Twister (p=521) to Random. All existing Random instances are migrated to the new implementation.

=============== Diff against Kernel-topa.905 ===============

Item was changed:
  Object subclass: #Random
+ 	instanceVariableNames: 'seed states index'
+ 	classVariableNames: 'A M MTa MTbShifted MTcShifted MTl MTlowerMask MTm MTn MTs MTt MTu MTupperMask MTw MTwFloatMultiplier MTwordMask Q R'
- 	instanceVariableNames: 'seed'
- 	classVariableNames: 'A M Q R'
  	poolDictionaries: ''
  	category: 'Kernel-Numbers'!
  
  !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.
  
  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>>bucketTest: (in category 'testing') -----
  bucketTest: randy
  	"Execute this:   Random bucketTest: Random new"
  	" 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 |
  	nbuckets := 200.
  	buckets := Array new: nbuckets.
  	buckets atAllPut: 0.
+ 	ntrys :=  10000.
- 	ntrys :=  1000.
  	ntrys*nbuckets timesRepeat: [ | slot |
+ 		slot := randy nextInt: nbuckets.
- 		slot := (randy next * nbuckets) floor + 1.
  		buckets at: slot put: (buckets at: slot) + 1 ].
  	Transcript cr.
  	1 to: nbuckets do: [ :nb |
  		Transcript print: (buckets at: nb); space ].
  	Transcript flush!

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.
+ 	self allInstancesDo: [ :each | each instVarNamed: #seed put: nil; seed: nil ]!
- 	"Initialize the magic constants. All instances share these values. Use floats to avoid LargeInteger computations (it still gives about 3-4x speedup)."
- 	
- 	A := 16807.0. " magic constant = 16807 "
- 	M := 2147483647.0. " magic constant = 2147483647 "
- 	Q := 127773.0. "(m quo: a) asFloat."
- 	R  :=  2836.0 "(m \\ a) asFloat."!

Item was changed:
  ----- Method: Random class>>seed: (in category 'instance creation') -----
+ seed: anInteger
+ 
- seed: anInteger 
  	^self basicNew seed: anInteger!

Item was added:
+ ----- Method: Random>>generateStates (in category 'private') -----
+ generateStates
+ 	"Generate untempered numbers into the states variable. Split up the operation into three parts to avoid the use of #atWrap: for accessing the states array. Optimized for SmallInteger operations."
+ 
+ 	| i limit y offset |
+ 	"Part 1"
+ 	i := 0.
+ 	offset := MTm.
+ 	limit := MTn - offset.
+ 	[ (i := i + 1) <= limit ] whileTrue: [
+ 		y := (MTupperMask bitAnd: (states at: i)) bitOr: (MTlowerMask bitAnd: (states at: i + 1)).
+ 		states
+ 			at: i
+ 			put: ((y bitAnd: 1) * MTa bitXor: ((states at: i + offset) bitXor: (y bitShift: -1))) ].
+ 	"Part 2"
+ 	limit := MTn - 1.
+ 	offset := MTm - MTn.
+ 	i := i - 1.
+ 	[ (i := i + 1) <= limit ] whileTrue: [
+ 		y := (MTupperMask bitAnd: (states at: i)) bitOr: (MTlowerMask bitAnd: (states at: i + 1)).
+ 		states
+ 			at: i
+ 			put: ((y bitAnd: 1) * MTa bitXor: ((states at: i + offset) bitXor: (y bitShift: -1))) ].
+ 	"Part 3"
+ 	y := (MTupperMask bitAnd: (states at: MTn)) bitOr: (MTlowerMask bitAnd: (states at: 1)).
+ 	states
+ 		at: MTn
+ 		put: ((y bitAnd: 1) * MTa bitXor: ((states at: MTm) bitXor: (y bitShift: -1))).
+ 	index := 1
+ 	!

Item was changed:
+ ----- Method: Random>>hashSeed: (in category 'private') -----
- ----- Method: Random>>hashSeed: (in category 'initialization') -----
  hashSeed: anInteger
+ 	"Use the 32-bit version of the FNV-1a algorithm to hash the seed, and return a 32-bit unsigned integer."
- 	" Use the 32-bit version of the FNV-1a algorithm to hash the seed. Keep only 31 bits during the calculation. "
  
  	| fnvPrime hash |
  	fnvPrime := 16777619 " 32-bit FVN prime ".
  	hash := anInteger negative
+ 		ifTrue: [  3490449840 "  mix in the sign as (2166136261 bitXor: 2r1010101) * 16777619 bitAnd: 16rFFFFFFFF "]
- 		ifTrue: [ 1342966192 "  mix in the sign as (2166136261 bitXor: 2r1010101) * 16777619 bitAnd: 16r7FFFFFFF "]
  		ifFalse: [ 2166136261 " 32-bit FVN offset basis "].
  	1 to: anInteger digitLength do: [ :index |
+ 		hash := 16rFFFFFFFF bitAnd: (hash bitXor: (anInteger digitAt: index)) * fnvPrime ].
+ 	^hash!
- 		hash := (hash bitXor: (anInteger digitAt: index)) * fnvPrime bitAnd: 16r7FFFFFFF ].
- 	seed := hash asFloat!

Item was changed:
  ----- Method: Random>>initialize (in category 'initialization') -----
  initialize
- 	" Set a reasonable Park-Miller starting seed "
  	
+ 	self seed: seed!
- 	| hash newSeed |
- 	hash := self hash hashMultiply.
- 	newSeed := Time primUTCMicrosecondClock.
- 	newSeed isZero ifTrue: [ " microsecond clock not available "
- 		newSeed := Time millisecondClockValue ].
- 	seed := ((newSeed bitAnd: 16r7FFFFFFF) bitXor: hash) asFloat!

Item was added:
+ ----- 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 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"!
- 	"Answer a random Float in the interval [0 to 1)."
- 
- 	^ (seed := self nextValue) - 1.0 / M!

Item was changed:
  ----- Method: Random>>nextInt: (in category 'accessing') -----
  nextInt: anInteger
+ 	"Answer a random integer value from the interval [1, anInteger]"
- 	" Answer a random integer in the interval [1, anInteger]. anInteger should be less than 16r80000000. "
  
+ 	| 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!
- 	"avoid Float arithmetic in #next to work with LargeInts"
- 	^ ((seed := self nextValue) asInteger * anInteger // M asInteger) + 1!

Item was added:
+ ----- Method: Random>>nextLargeInt: (in category 'accessing') -----
+ nextLargeInt: anInteger
+ 	"Answer a random integer value from the interval [1, anInteger]. This method works for arbitrarily large integers."
+ 
+ 	| byteCount bigRandom remainder remainingBits i result firstDigit |
+ 	byteCount := anInteger digitLength + 4. "Extend the space with at least 32 bits for a fairer distribution."
+ 	bigRandom := LargePositiveInteger new: byteCount.
+ 	remainder := remainingBits := 0.
+ 	i := 1.
+ 	[ i <= byteCount ] whileTrue: [
+ 		remainingBits >= 8
+ 			ifTrue: [
+ 				bigRandom digitAt: i put: (remainder bitAnd: 16rFF).
+ 				remainder := remainder bitShift: -8.
+ 				remainingBits := remainingBits - 8.
+ 				i := i + 1 ]
+ 			ifFalse: [
+ 				remainingBits = 0
+ 					ifTrue: [ remainder := self nextValue ]
+ 					ifFalse: [
+ 						| newRandom |
+ 						newRandom := self nextValue.
+ 						bigRandom digitAt: i put: (remainder bitShift: 8 - remainingBits) + 
+ 							(newRandom bitAnd: (1 bitShift: 8 - remainingBits) - 1).
+ 						i := i + 1.
+ 						remainder := newRandom bitShift: 0 - remainingBits ].
+ 				remainingBits := MTw - remainingBits ] ].
+ 	result := anInteger * bigRandom bitShift: -8 * byteCount.
+ 	"Avoid using LargeInteger arithmetic for +1 in most cases."
+ 	result isLarge ifFalse: [ ^result + 1 ].
+ 	(firstDigit := result digitAt: 1) = 255 ifTrue: [ ^result + 1 ].
+ 	result digitAt: 1 put: firstDigit + 1.
+ 	^result
+ 	!

Item was changed:
  ----- Method: Random>>nextValue (in category 'private') -----
  nextValue
+ 	"Answer an MTw-bit random integer between 0 and wordMask, and increment the index."
- 	"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)."
  
+ 	| 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!
- 	| 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!

Item was changed:
  ----- Method: Random>>seed: (in category 'initialization') -----
+ seed: anIntegerOrNil
+ 	" Use the given integer as seed, or generate one if it's nil. "
- seed: anInteger
- 	" Use this 31-bit nonnegative integer as seed. Generate a valid seed using a hash function if it's out of range. "
  
+ 	| newSeed |
+ 	newSeed := anIntegerOrNil ifNil: [
+ 		| now |
+ 		now := Time primUTCMicrosecondClock.
+ 		now = 0 ifTrue: [ now := Time millisecondClockValue ].
+ 		(now bitShift: 28) bitXor: self hash hashMultiply ].
+ 	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 
+ 		initializeStates;
+ 		generateStates!
- 	(anInteger between: 0 and: 16r7FFFFFFF)
- 		ifTrue: [ seed := anInteger asFloat ]
- 		ifFalse: [ self hashSeed: anInteger ]!



More information about the Squeak-dev mailing list