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

Levente Uzonyi leves at elte.hu
Mon Sep 23 21:35:13 UTC 2013


I put this to the Inbox, because the Trunk is unstable.


Levente

On Mon, 23 Sep 2013, commits at source.squeak.org wrote:

> A new version of Kernel was added to project The Inbox:
> http://source.squeak.org/inbox/Kernel-ul.811.mcz
>
> ==================== Summary ====================
>
> Name: Kernel-ul.811
> Author: ul
> Time: 23 September 2013, 6:48:32.356 pm
> UUID: b32f1827-e63d-46dd-b6b9-0a15355aac6a
> Ancestors: Kernel-nice.810
>
> Changed Random for faster instance creation and better randomness:
> - moved constants q, r, a and m to class variables. There's no need to calculate and store them in all instances. Haven't inlined them, so they are documented and defined in one place.
> - try to use #primUTCMicrosecondClock for seed generation
> - don't calculate seed, when the user provides it
> - updated constants in #bucketTest:, because machines are faster nowadays
>
> =============== Diff against Kernel-nice.810 ===============
>
> Item was changed:
>  Object subclass: #Random
> + 	instanceVariableNames: 'seed'
> + 	classVariableNames: 'A M Q R'
> - 	instanceVariableNames: 'seed a m q r'
> - 	classVariableNames: ''
>  	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.
> - 	nbuckets := 20.
>  	buckets := Array new: nbuckets.
>  	buckets atAllPut: 0.
> + 	ntrys :=  1000.
> - 	ntrys :=  100.
>  	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 show: (buckets at: nb) printString, ' ' ]!
>
> Item was added:
> + ----- Method: Random class>>initialize (in category 'class initialization') -----
> + initialize
> + 	"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
> + 	^self basicNew seed: anInteger!
> - 	^self new seed: anInteger!
>
> Item was changed:
>  ----- Method: Random>>initialize (in category 'initialization') -----
>  initialize
> +
> + 	| 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 ]!
> - 	" Set a reasonable Park-Miller starting seed "
> - 	[seed := (Time millisecondClockValue bitAnd: 16r3FFFFFFF) bitXor: self hash.
> - 	seed = 0] whileTrue: ["Try again if ever get a seed = 0"].
> -
> - 	a := 16r000041A7 asFloat.    " magic constant =      16807 "
> - 	m := 16r7FFFFFFF asFloat.    " magic constant = 2147483647 "
> - 	q := (m quo: a) asFloat.
> - 	r  := (m \\ a) asFloat.
> - !
>
> Item was changed:
>  ----- Method: Random>>next (in category 'accessing') -----
>  next
>  	"Answer a random Float in the interval [0 to 1)."
>
> + 	^ (seed := self nextValue) / M!
> - 	^ (seed := self nextValue) / m!
>
> Item was changed:
>  ----- Method: Random>>nextValue (in category 'private') -----
>  nextValue
>  	"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 answer |
> + 	hi := (seed quo: Q) asFloat.
> + 	lo := seed - (hi * Q).  " = seed rem: q"
> + 	aLoRHi := (A * lo) - (R * hi).
> - 	hi := (seed quo: q) asFloat.
> - 	lo := seed - (hi * q).  " = seed rem: q"
> - 	aLoRHi := (a * lo) - (r * hi).
>  	answer := (aLoRHi > 0.0)
>  		ifTrue:  [aLoRHi]
> + 		ifFalse: [aLoRHi + M].
> - 		ifFalse: [aLoRHi + m].
>  	^ answer!
>
>
>


More information about the Squeak-dev mailing list