[squeak-dev] The Inbox: Kernel-ul.874.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Sep 21 17:26:11 UTC 2014


A new version of Kernel was added to project The Inbox:
http://source.squeak.org/inbox/Kernel-ul.874.mcz

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

Name: Kernel-ul.874
Author: ul
Time: 21 September 2014, 7:24:24.087 pm
UUID: b39db5fc-8e25-4059-98d5-5ffbdd608e76
Ancestors: Kernel-nice.873

Random changes:
- fixed off-by-one error in #next
- seed is always a Float
- added #hashSeed: which can be used to produce a better initial seed. Small seeds will result in less random first value.
- seed is forced between 0 and 2^31-1 if it's out of range using #hashSeed:
- simplified #initialize. 0 is not a bad seed value
- fixed #nextValue's comment and simplified the implementation a bit
- added clarification to #nextInt:'s comment
- sped up #bucketTest: on the class side

=============== Diff against Kernel-nice.873 ===============

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 :=  1000.
  	ntrys*nbuckets timesRepeat: [ | slot |
  		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!
- 		Transcript show: (buckets at: nb) printString, ' ' ]!

Item was added:
+ ----- Method: Random>>hashSeed: (in category 'initialization') -----
+ hashSeed: anInteger
+ 	" 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: [ 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 := (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 "
  	
+ 	| 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!
- 	| hash |
- 	hash := self hash.
- 	"Set a reasonable Park-Miller starting seed"
- 	seed := Time primUTCMicrosecondClock.
- 	seed = 0 ifFalse: [ "Use the microsecond clock if possible."
- 		seed := (seed bitAnd: 16r3FFFFFFF) bitXor: hash ].
- 	[ seed = 0 ] whileTrue: [ "Try again if ever get a seed = 0, or there's no microsecond clock."
- 		seed := (Time millisecondClockValue bitAnd: 16r3FFFFFFF) bitXor: hash ]!

Item was changed:
  ----- Method: Random>>next (in category 'accessing') -----
  next
  	"Answer a random Float in the interval [0 to 1)."
  
+ 	^ (seed := self nextValue) - 1.0 / M!
- 	^ (seed := self nextValue) / M!

Item was changed:
  ----- Method: Random>>nextInt: (in category 'accessing') -----
  nextInt: anInteger
+ 	" Answer a random integer in the interval [1, anInteger]. anInteger should be less than 16r80000000. "
- 	"Answer a random integer in the interval [1, anInteger]."
  
  	anInteger strictlyPositive ifFalse: [ self error: 'Range must be positive' ].
  	^ (self next * anInteger) truncated + 1!

Item was changed:
  ----- Method: Random>>nextValue (in category 'private') -----
  nextValue
+ 	"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.
- 	"This method generates random instances of Integer 	in the interval
- 	0 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"  
- 	| lo hi aLoRHi answer |
- 	hi := (seed quo: Q) asFloat.
- 	lo := seed - (hi * Q).  " = seed rem: q"  
  	aLoRHi := (A * lo) - (R * hi).
+ 	aLoRHi > 0.0 ifTrue: [ ^aLoRHi ].
+ 	^aLoRHi + M!
- 	answer := (aLoRHi > 0.0)
- 		ifTrue:  [aLoRHi]
- 		ifFalse: [aLoRHi + M].
- 	^ answer!

Item was changed:
  ----- Method: Random>>seed: (in category 'initialization') -----
+ seed: anInteger
+ 	" Use this 31-bit nonnegative integer as seed. Generate a valid seed using a hash function if it's out of range. "
+ 
+ 	(anInteger between: 0 and: 16r7FFFFFFF)
+ 		ifTrue: [ seed := anInteger asFloat ]
+ 		ifFalse: [ self hashSeed: anInteger ]!
- seed: anInteger 
- 	seed := anInteger!



More information about the Squeak-dev mailing list