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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 31 07:40:53 UTC 2022


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

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

Name: Kernel-ul.1454
Author: ul
Time: 31 March 2022, 9:40:35.561194 am
UUID: 77c53e53-4088-4309-9dcf-a2ea77469e41
Ancestors: Kernel-ct.1453

- do not try to compact immutable MethodDictionaries in #compactAllInstances
- update the tally first when modifying a MethodDictionary, so that immutable MethodDictionaries raise an error before their non-immutable array variable is updated
- do not send #rounded to #sign in Float >> #rounded. #sign is already rounded
- use Symboll class >> #lookup: instead of #hasInterned:ifTrue:
- use #anySatisfy: instead of reinventing it in Object >> #inheritsFromAnyIn:. Also, use #classNamed: to look up a class in the same method.

=============== Diff against Kernel-ct.1453 ===============

Item was changed:
  ----- Method: Behavior>>whichClassDefinesClassVar: (in category 'queries') -----
  whichClassDefinesClassVar: aString 
+ 
+ 	^(Symbol lookup: aString) ifNotNil: [ :aSymbol |
- 	Symbol hasInterned: aString ifTrue: [ :aSymbol |
  		^self whichSuperclassSatisfies: 
  			[:aClass | 
+ 			aClass classVarNames anySatisfy: [:each | each = aSymbol]]]!
- 			aClass classVarNames anySatisfy: [:each | each = aSymbol]]].
- 	^nil!

Item was changed:
  ----- Method: Float>>rounded (in category 'truncation and round off') -----
  rounded
  	"Answer the integer nearest the receiver.
  	Implementation note: super would not handle tricky inexact arithmetic"
  	
  	"self assert: 5000000000000001.0 rounded = 5000000000000001"
  
  	self fractionPart abs < 0.5
  		ifTrue: [^self truncated]
+ 		ifFalse: [^self truncated + self sign]!
- 		ifFalse: [^self truncated + self sign rounded]!

Item was changed:
  ----- Method: MethodDictionary class>>compactAllInstances (in category 'initialize-release') -----
  compactAllInstances
  
  	| instancesToExchange newInstances |
  	instancesToExchange := Array streamContents: [ :oldStream |
  		newInstances := Array streamContents: [ :newStream |
  			self allInstances do: [ :each |
+ 				each isReadOnlyObject ifFalse: [
+ 					| newInstance |
+ 					newInstance := each compactWithoutBecome.
+ 					newInstance capacity = each capacity 
+ 						ifTrue: [ each copyFrom: newInstance ]
+ 						ifFalse: [
+ 							oldStream nextPut: each.
+ 							newStream nextPut: newInstance ] ] ] ] ].
- 				| newInstance |
- 				newInstance := each compactWithoutBecome.
- 				newInstance capacity = each capacity 
- 					ifTrue: [ each copyFrom: newInstance ]
- 					ifFalse: [
- 						oldStream nextPut: each.
- 						newStream nextPut: newInstance ] ] ] ].
  	instancesToExchange elementsForwardIdentityTo: newInstances!

Item was changed:
  ----- Method: MethodDictionary>>removeDangerouslyKey:ifAbsent: (in category 'private') -----
  removeDangerouslyKey: key ifAbsent: aBlock
  	"This is not really dangerous.  But if normal removal
  	were done WHILE a MethodDict were being used, the
  	system might crash.  So instead we make a copy, then do
  	this operation (which is NOT dangerous in a copy that is
  	not being used), and then use the copy after the removal."
  
  	| index element |
  	index := self scanFor: key.
  	(element := array at: index) ifNil: [ ^aBlock value ].
+ 	tally := tally - 1. "Update tally first, so that read-only hashed collections raise an error before modifying array."
  	array at: index put: nil.
  	self basicAt: index put: nil.
- 	tally := tally - 1.
  	self fixCollisionsFrom: index.
  	^element!

Item was changed:
  ----- Method: Object>>inheritsFromAnyIn: (in category 'class membership') -----
  inheritsFromAnyIn: aList
  	"Answer whether the receiver inherits from any class represented by any element in the list.  The elements of the list can be classes, class name symbols, or strings representing possible class names.  This allows speculative membership tests to be made even when some of the classes may not be known to the current image, and even when their names are not interned symbols."
  
+ 	^aList anySatisfy: [ :element |
+ 		(Smalltalk classNamed: element asString)
+ 			ifNil: [ false ]
+ 			ifNotNil: [ :class |
+ 				(class isKindOf: Class)
+ 					and: [ self isKindOf: class ] ] ]
- 	aList do:
- 		[:elem | Symbol hasInterned: elem asString ifTrue: 
- 			[:elemSymbol |
- 			| aClass |
- 			(((aClass := Smalltalk at: elemSymbol ifAbsent: [nil]) isKindOf: Class)
- 						and: [self isKindOf: aClass])
- 				ifTrue:
- 					[^ true]]].
- 	^ false
  
- 
  "
  {3.  true. 'olive'} do:
  	[:token |
  		 {{#Number. #Boolean}. {Number.  Boolean }.  {'Number'. 'Boolean'}} do:
  			[:list |
  				Transcript cr; show: token asString, ' list element provided as a ', list first class name, ' - ', (token inheritsFromAnyIn: list) asString]]
  "!



More information about the Squeak-dev mailing list