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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 24 16:26:40 UTC 2013


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

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

Name: Kernel-ul.812
Author: ul
Time: 24 October 2013, 6:20:30.715 pm
UUID: c9549364-8b71-4105-ac51-cff717cd57ee
Ancestors: Kernel-nice.811, Kernel-ul.811

- merged Kernel-ul.811 with the changes to Random
- use the #environment message to access the environment from Class, instead of the variable named environment, because the latter might be nil, which causes an error during update

=============== Diff against Kernel-nice.811 ===============

Item was changed:
  ----- Method: Class>>removeClassVarName: (in category 'class variables') -----
  removeClassVarName: aString 
  	"Remove the class variable whose name is the argument, aString, from 
  	the names defined in the receiver, a class. Create an error notification if 
  	aString is not a class variable or if it is still being used in the code of 
  	the class."
  
  	| aSymbol |
  	aSymbol := aString asSymbol.
  	(classPool includesKey: aSymbol)
  		ifFalse: [^self error: aString, ' is not a class variable'].
  	self withAllSubclasses do:[:subclass |
  		(Array with: subclass with: subclass class) do:[:classOrMeta |
  			(classOrMeta whichSelectorsReferTo: (classPool associationAt: aSymbol))
  				isEmpty ifFalse: [
  					InMidstOfFileinNotification signal ifTrue: [
  						Transcript cr; show: self name, ' (' , aString , ' is Undeclared) '.
+ 						^self environment undeclared declare: aSymbol from: classPool].
- 						^ environment undeclared declare: aSymbol from: classPool].
  					(self confirm: (aString,' is still used in code of class ', classOrMeta name,
  						'.\Is it okay to move it to Undeclared?') withCRs)
  						ifTrue:[^Undeclared declare: aSymbol from: classPool]
  						ifFalse:[^self]]]].
  	classPool removeKey: aSymbol.
  	classPool isEmpty ifTrue: [classPool := nil].
  !

Item was changed:
  ----- Method: Class>>rename: (in category 'class name') -----
  rename: aString 
  	"The new name of the receiver is the argument, aString."
  
  	| oldName newName |
  	(newName := aString asSymbol) = (oldName := self name)
  		ifTrue: [^ self].
  	(self environment includesKey: newName)
  		ifTrue: [^ self error: newName , ' already exists'].
+ 	(self environment undeclared includesKey: newName)
- 	(environment undeclared includesKey: newName)
  		ifTrue: [self inform: 'There are references to ' , aString printString , '
  from Undeclared. Check them after this change.'].
  	name := newName.
  	self environment renameClass: self from: oldName!

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