[squeak-dev] The Trunk: Kernel-nice.291.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Nov 10 20:55:20 UTC 2009


Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.291.mcz

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

Name: Kernel-nice.291
Author: nice
Time: 10 November 2009, 9:53:23 am
UUID: 3e5cd2e5-3e74-4398-a409-8e02189e9cec
Ancestors: Kernel-nice.290

Finish fixing comparison of MethodProperties and AdditionalMethodState for debug purpose

MethodProperties is candidate for being removed.
But it still has a few instances.

After fixing comparison, I can remove some with:

(MethodContext allInstances select: [:e | e method notNil
    and: [ e method isInstalled not
    and: [(e method methodClass notNil)
    and: [(e method methodClass includesSelector: e method selector)
    and: [e method = (e method methodClass >> e method selector)]]]]])
  do: [:mc | mc instVarNamed: #method put:
    (mc method methodClass >> mc method selector)]

A more efficient weapon for eliminating MethodProperties is 

Utilities postRecompileCleanup.
MethodProperties allInstances size -> 0

=============== Diff against Kernel-nice.290 ===============

Item was changed:
  ----- Method: MethodProperties>>analogousCodeTo: (in category 'testing') -----
  analogousCodeTo: aMethodProperties
  	pragmas
  		ifNil: [aMethodProperties pragmas notEmpty ifTrue: [^false]]
  		ifNotNil:
+ 			[pragmas size ~= aMethodProperties pragmas size ifTrue:
- 			[aMethodProperties pragmas isEmpty ifTrue: [^false].
- 			 pragmas size ~= aMethodProperties pragmas size ifTrue:
  				[^false].
  			 pragmas with: aMethodProperties pragmas do:
  				[:mine :others|
  				(mine analogousCodeTo: others) ifFalse: [^false]]].
  	^(self hasAtLeastTheSamePropertiesAs: aMethodProperties)
  	  and: [aMethodProperties hasAtLeastTheSamePropertiesAs: self]!

Item was changed:
  ----- Method: CompiledMethod>>= (in category 'comparing') -----
  = method
  	| numLits |
  	"Answer whether the receiver implements the same code as the 
  	argument, method."
  	(method isKindOf: CompiledMethod) ifFalse: [^false].
  	self size = method size ifFalse: [^false].
  	self header = method header ifFalse: [^false].
  	self initialPC to: self endPC do:
  		[:i | (self at: i) = (method at: i) ifFalse: [^false]].
  	(numLits := self numLiterals) ~= method numLiterals ifTrue: [^false].
  	"``Dont bother checking FFI and named primitives''
  	 (#(117 120) includes: self primitive) ifTrue: [^ true]."
  	1 to: numLits do:
  		[:i| | lit1 lit2 |
  		lit1 := self literalAt: i.
  		lit2 := method literalAt: i.
  		lit1 = lit2 ifFalse:
  			[(i = 1 and: [#(117 120) includes: self primitive])
  				ifTrue: [lit1 isArray
  							ifTrue:
  								[(lit2 isArray and: [lit1 allButLast = lit2 allButLast]) ifFalse:
  									[^false]]
  							ifFalse: "ExternalLibraryFunction"
  								[(lit1 analogousCodeTo: lit2) ifFalse:
  									[^false]]] ifFalse:
  			[i = (numLits - 1) ifTrue: "properties"
+ 				[(self properties analogousCodeTo: method properties) ifFalse:
- 				[(lit1 analogousCodeTo: lit2) ifFalse:
  					[^false]] ifFalse:
  			 [lit1 isFloat
  				ifTrue:
  					["Floats match if values are close, due to roundoff error."
  					(lit1 closeTo: lit2) ifFalse: [^false]. self flag: 'just checking'. self halt]
  				ifFalse:
  					["any other discrepancy is a failure"
  					^ false]]]]].
  	^true!




More information about the Squeak-dev mailing list