[Vm-dev] VM Maker: VMMaker.oscog-eem.883.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 25 01:37:30 UTC 2014


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.883.mcz

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

Name: VMMaker.oscog-eem.883
Author: eem
Time: 24 September 2014, 6:34:42.166 pm
UUID: a585d66e-f0cd-42cd-ad84-5cc861a20f9e
Ancestors: VMMaker.oscog-eem.882

Spur:
Change become to flush method caches for
becommed classes.

I'm not sure this is necessary but strangely the new
code is faster than 882 for the Newspeak bootstrap.
So I'm committing this to allow me to compare the
two.

Changes are to
- add a BecameActiveClassFlag to becomeEffectsFlags
- refuse to do an in-place become on active classes.
- flush the caches before the post-become scan of
the class table so that forwarded classes can be
spotted.  i.e. if a class index in a method cache is that
of a forwarded class then it was becommed and the
cache entry can be voided.

=============== Diff against VMMaker.oscog-eem.882 ===============

Item was changed:
  SystemOrganization addCategory: #'VMMaker-Building'!
  SystemOrganization addCategory: #'VMMaker-Interpreter'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation'!
  SystemOrganization addCategory: #'VMMaker-InterpreterSimulation-Morphic'!
  SystemOrganization addCategory: #'VMMaker-JIT'!
  SystemOrganization addCategory: #'VMMaker-JITSimulation'!
  SystemOrganization addCategory: #'VMMaker-Multithreading'!
  SystemOrganization addCategory: #'VMMaker-Plugins'!
  SystemOrganization addCategory: #'VMMaker-Plugins-Alien'!
+ SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!
  SystemOrganization addCategory: #'VMMaker-PostProcessing'!
  SystemOrganization addCategory: #'VMMaker-SmartSyntaxPlugins'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManager'!
  SystemOrganization addCategory: #'VMMaker-SpurMemoryManagerSimulation'!
  SystemOrganization addCategory: #'VMMaker-Support'!
  SystemOrganization addCategory: #'VMMaker-Tests'!
  SystemOrganization addCategory: #'VMMaker-Translation to C'!
- SystemOrganization addCategory: #'VMMaker-Plugins-IOS'!

Item was added:
+ ----- Method: CoInterpreter>>flushBecommedClassesInMethodZone (in category 'object memory support') -----
+ flushBecommedClassesInMethodZone
+ 	<inline: true>
+ 	cogit unlinkSendsToForwardedClasses!

Item was added:
+ ----- Method: Cogit>>cPICHasForwardedClass: (in category 'in-line cacheing') -----
+ cPICHasForwardedClass: cPIC
+ 	<var: #cPIC type: #'CogMethod *'>
+ 	| pc |
+ 	pc := cPIC asInteger + firstCPICCaseOffset.
+ 	1 to: cPIC cPICNumCases do:
+ 		[:i| | classIndex |
+ 		classIndex := backEnd inlineCacheTagAt: pc
+ 												- backEnd jumpLongConditionalByteSize
+ 												- backEnd loadLiteralByteSize.
+ 		(objectMemory isForwardedClassIndex: classIndex) ifTrue:
+ 			[^true].
+ 		pc := pc + cPICCaseSize].
+ 	^false!

Item was added:
+ ----- Method: Cogit>>isSuperSend: (in category 'in-line cacheing') -----
+ isSuperSend: entryPoint
+ 	<inline: true>
+ 	^(entryPoint bitAnd: entryPointMask) ~= checkedEntryAlignment!

Item was added:
+ ----- Method: Cogit>>unlinkIfForwardedSend:pc:ignored: (in category 'in-line cacheing') -----
+ unlinkIfForwardedSend: annotation pc: mcpc ignored: superfluity
+ 	<var: #mcpc type: #'char *'>
+ 	| entryPoint cacheAddress |
+ 	(self isSendAnnotation: annotation) ifTrue:
+ 		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 entryPoint > methodZoneBase
+ 			ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
+ 				[(objectMemory isForwardedClassIndex: (backEnd inlineCacheTagAt: mcpc)) ifTrue:
+ 					[self targetMethodAndSendTableFor: entryPoint into:
+ 						[:targetMethod :sendTable|
+ 						 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]
+ 			ifFalse:
+ 				[self cppIf: NewspeakVM ifTrue:
+ 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 						[self assert: NumOopsPerIRC = 2.
+ 						 cacheAddress := self implicitReceiverCacheAddressAt: mcpc.
+ 						 ((objectMemory isForwardedClassIndex: (backEnd unalignedLongAt: cacheAddress))
+ 						 or: [objectMemory isForwardedClassIndex: (backEnd unalignedLongAt: cacheAddress + BytesPerOop)]) ifTrue:
+ 							[self voidImplicitReceiverCacheAt: mcpc]]]]].
+ 	^0 "keep scanning"!

Item was added:
+ ----- Method: Cogit>>unlinkSendsToForwardedClasses (in category 'jit - api') -----
+ unlinkSendsToForwardedClasses
+ 	<api>
+ 	<option: #SpurObjectMemory>
+ 	"Unlink all sends in cog methods whose class tag is that of a forwarded class."
+ 	| cogMethod freedPIC |
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	methodZoneBase ifNil: [^self].
+ 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	codeModified := freedPIC := false.
+ 	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod cmType = CMMethod
+ 			ifTrue:
+ 				[self mapFor: cogMethod
+ 					 performUntil: #unlinkIfForwardedSend:pc:ignored:
+ 					 arg: 0]
+ 			ifFalse:
+ 				[(cogMethod cmType = CMClosedPIC
+ 				  and: [self cPICHasForwardedClass: cogMethod]) ifTrue:
+ 					[methodZone freeMethod: cogMethod.
+ 					 freedPIC := true]].
+ 		cogMethod := methodZone methodAfter: cogMethod].
+ 	freedPIC
+ 		ifTrue: [self unlinkSendsToFree]
+ 		ifFalse:
+ 			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 				[processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>isForwardedClassIndex: (in category 'class table') -----
+ isForwardedClassIndex: maybeClassIndex
+ 	"A lenient tester of forwarded class indices for inline cache management in the Cogit."
+ 	<api>
+ 	| classTablePage entry |
+ 	maybeClassIndex asUnsignedInteger >= self classTableRootSlots ifTrue:
+ 		[^false].
+ 	classTablePage := self fetchPointer: maybeClassIndex >> self classTableMajorIndexShift
+ 							ofObject: hiddenRootsObj.
+ 	classTablePage = nilObj ifTrue:
+ 		[^false].
+ 	entry := self
+ 				fetchPointer: (maybeClassIndex bitAnd: self classTableMinorIndexMask)
+ 				ofObject: classTablePage.
+ 	^self isForwarded: entry!

Item was changed:
  ----- Method: SpurMemoryManager class>>initializeSpurObjectRepresentationConstants (in category 'class initialization') -----
  initializeSpurObjectRepresentationConstants
  	"SpurMemoryManager initializeSpurObjectRepresentationConstants"
  	BecamePointerObjectFlag := 1.
  	BecameCompiledMethodFlag := 2.
  	OldBecameNewFlag := 4.
+ 	BecameActiveClassFlag := 8 "For flushing method caches"!
- 	"BecameClassFlag := 8" "this turns out not to be actionable"
- !

Item was changed:
  ----- Method: SpurMemoryManager>>become:with:twoWay:copyHash: (in category 'become api') -----
  become: array1 with: array2 twoWay: twoWayFlag copyHash: copyHashFlag
  	"All references to each object in array1 are swapped with all references to the
  	 corresponding object in array2. That is, all pointers to one object are replaced
  	 with with pointers to the other. The arguments must be arrays of the same length. 
  	 Answers PrimNoErr if the primitive succeeds, otherwise a relevant error code."
  	"Implementation: Uses lazy forwarding to defer updating references until message send."
  	| ec |
  	self assert: becomeEffectsFlags = 0.
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  	(self isArray: array1) ifFalse:
  		[^PrimErrBadReceiver].
  	((self isArray: array2)
  	 and: [(self numSlotsOf: array1) = (self numSlotsOf: array2)]) ifFalse:
  		[^PrimErrBadArgument].
  	(twoWayFlag or: [copyHashFlag])
  		ifTrue:
  			[ec := self containsOnlyValidBecomeObjects: array1 and: array2]
  		ifFalse:
  			[self followForwardedObjectFields: array2 toDepth: 0.
  			ec := self containsOnlyValidBecomeObjects: array1].
  	ec ~= 0 ifTrue: [^ec].
  
  	coInterpreter preBecomeAction.
  	twoWayFlag
  		ifTrue:
  			[self innerBecomeObjectsIn: array1 and: array2 copyHash: copyHashFlag]
  		ifFalse:
  			[self innerBecomeObjectsIn: array1 to: array2 copyHash: copyHashFlag].
  	self followSpecialObjectsOop.
+ 	"N.B. perform coInterpreter's postBecomeAction: *before* postBecomeScanClassTable:
+ 	 to allow the coInterpreter to void method cache entries by spotting classIndices that
+ 	 refer to forwarded objects. postBecomeScanClassTable: follows forwarders in the table."
- 	self postBecomeScanClassTable: becomeEffectsFlags.
  	coInterpreter postBecomeAction: becomeEffectsFlags.
+ 	self postBecomeScanClassTable: becomeEffectsFlags.
  	becomeEffectsFlags := 0.
  
  	self assert: self validClassTableHashes.
  	self leakCheckBecome ifTrue:
  		[self runLeakCheckerForFullGC: true].
  
  	^PrimNoErr "success"!

Item was changed:
  ----- Method: SpurMemoryManager>>becomeEffectFlagsFor: (in category 'become implementation') -----
  becomeEffectFlagsFor: objOop
  	"Answer the appropriate become effect flags for objOop, or 0 if none.
+ 	 The effect flags determine how much work is done after the become
+ 	 in following forwarding pointers, voiding method caches, etc."
- 	 The effect flags affect how much work is done after the become in
- 	 following forwarding pointers."
  	<inline: false>
  	^(self isPointersNonImm: objOop)
  		ifTrue:
+ 			[| hash |
+ 			 ((hash := self rawHashBitsOf: objOop) ~= 0
+ 			  and: [(self classAtIndex: hash) = objOop])
+ 				ifTrue: [BecamePointerObjectFlag + BecameActiveClassFlag]
+ 				ifFalse: [BecamePointerObjectFlag]]
- 			[BecamePointerObjectFlag
- 			"older code that identified class objects, but it isn't helpful:"
- 			"| hash |
- 			 (hash := self rawHashBitsOf: objOop) = 0
- 				ifTrue: ""Can't identify an abstract class by the class table; it may not be there-in.""
- 					[(coInterpreter objCouldBeClassObj: objOop)
- 						ifTrue: [BecamePointerObjectFlag + BecameClassFlag]
- 						ifFalse: [BecamePointerObjectFlag]]
- 				ifFalse: ""if an object has a hash and it's a class it must be in the table.""
- 					[(self classAtIndex: hash) = objOop
- 						ifTrue: [BecamePointerObjectFlag + BecameClassFlag]
- 						ifFalse: [BecamePointerObjectFlag]]"]
  		ifFalse:
  			[(self isCompiledMethod: objOop)
  				ifTrue: [BecameCompiledMethodFlag]
  				ifFalse: [0]]!

Item was changed:
  ----- Method: SpurMemoryManager>>doBecome:and:copyHash: (in category 'become implementation') -----
  doBecome: obj1 and: obj2 copyHash: copyHashFlag
  	"Inner dispatch for two-way become.
  	 N.B. At least in current two-way become use copyHashFlag is false."
  	| o1ClassIndex o2ClassIndex |
+ 	"in-lined
- 	copyHashFlag ifFalse:
- 		["in-lined
  			classIndex := (self isInClassTable: obj) ifTrue: [self rawHashBitsOf: obj] ifFalse: [0]
+ 	 for speed."
+ 	o1ClassIndex := self rawHashBitsOf: obj1.
+ 	(o1ClassIndex ~= 0 and: [(self classAtIndex: o1ClassIndex) ~= obj1]) ifTrue:
+ 		[o1ClassIndex := 0].
+ 	o2ClassIndex := self rawHashBitsOf: obj2.
+ 	(o2ClassIndex ~= 0 and: [(self classAtIndex: o2ClassIndex) ~= obj2]) ifTrue:
+ 		[o2ClassIndex := 0].
+ 
+ 	"Refuse to do an in-place become on classes since their being
+ 	 forwarded is used in the flush method cache implementations."
+ 	((self numSlotsOf: obj1) = (self numSlotsOf: obj2)
+ 	 and: [o1ClassIndex = 0
+ 	 and: [o2ClassIndex = 0]]) ifTrue:
- 		 for speed."
- 		 o1ClassIndex := self rawHashBitsOf: obj1.
- 		 (o1ClassIndex ~= 0 and: [(self classAtIndex: o1ClassIndex) ~= obj1]) ifTrue:
- 			[o1ClassIndex := 0].
- 		 o2ClassIndex := self rawHashBitsOf: obj2.
- 		 (o2ClassIndex ~= 0 and: [(self classAtIndex: o2ClassIndex) ~= obj2]) ifTrue:
- 			[o2ClassIndex := 0]].
- 	(self numSlotsOf: obj1) = (self numSlotsOf: obj2) ifTrue:
  		[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag.
- 		 self assert: (o1ClassIndex = 0
- 					or: [(self rawHashBitsOf: (self classAtIndex: o1ClassIndex)) = o1ClassIndex]).
- 		 self assert: (o2ClassIndex = 0
- 					or: [(self rawHashBitsOf: (self classAtIndex: o2ClassIndex)) = o2ClassIndex]).
  		 ^self].
  	self outOfPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag.
  	"if copyHashFlag then nothing changes, since hashes were also swapped."
  	copyHashFlag ifTrue:
  		[^self].
+ 	"if copyHash is false then the classTable entries must be updated.
+ 	 We leave the following until postBecomeScanClassTable:, but must
+ 	 swap the forwarders if two active classes have been becommed,
+ 	 and assign hashes if not."
- 	"if copyHash is false then the classTable entries must be updated."
  	o1ClassIndex ~= 0
  		ifTrue:
  			[o2ClassIndex ~= 0
+ 				ifTrue:
+ 					[self classAtIndex: o1ClassIndex put: obj2.
+ 					 self classAtIndex: o2ClassIndex put: obj1]
+ 				ifFalse: "o2 wasn't in the table; set its hash"
- 				ifTrue: "both were in the table; just swap entries"
- 					[| tmp |
- 					 tmp := self classAtIndex: o1ClassIndex.
- 					 self classAtIndex: o1ClassIndex put: obj2.
- 					 self classAtIndex: o2ClassIndex put: tmp]
- 				ifFalse: "o2 wasn't in the table; put it there"
  					[| newObj2 |
  					 newObj2 := self followForwarded: obj1.
  					 self assert: (self rawHashBitsOf: newObj2) = 0.
+ 					 self setHashBitsOf: newObj2 to: o1ClassIndex]]
- 					 self setHashBitsOf: newObj2 to: o1ClassIndex.
- 					 self classAtIndex: o1ClassIndex put: newObj2]]
  		ifFalse:
+ 			[o2ClassIndex ~= 0 ifTrue: "o1 wasn't in the table; set its hash"
- 			[o2ClassIndex ~= 0 ifTrue:
  				[| newObj1 |
  				 newObj1 := self followForwarded: obj2.
  				 self assert: (self rawHashBitsOf: newObj1) = 0.
+ 				 self setHashBitsOf: newObj1 to: o2ClassIndex]]!
- 				 self setHashBitsOf: newObj1 to: o2ClassIndex.
- 				 self classAtIndex: o2ClassIndex put: newObj1]]!

Item was changed:
  ----- Method: SpurMemoryManager>>inPlaceBecome:and:copyHashFlag: (in category 'become implementation') -----
  inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag
  	"Do become in place by swapping object contents."
  	| headerTemp temp1 temp2 o1HasYoung o2HasYoung fmt |
  	self assert: (self numSlotsOf: obj1) = (self numSlotsOf: obj2).
+ 	self assert: ((self rawHashBitsOf: obj1) = 0
+ 				 or: [(self classOrNilAtIndex: (self rawHashBitsOf: obj1)) ~= obj1]).
+ 	self assert: ((self rawHashBitsOf: obj2) = 0
+ 				 or: [(self classOrNilAtIndex: (self rawHashBitsOf: obj2)) ~= obj2]).
  	"swap headers, but swapping headers swaps remembered bits;
  	 these need to be unswapped."
  	temp1 := self isRemembered: obj1.
  	temp2 := self isRemembered: obj2.
  	headerTemp := self long64At: obj1.
  	self long64At: obj1 put: (self long64At: obj2).
  	self long64At: obj2 put: headerTemp.
  	self setIsRememberedOf: obj1 to: temp1.
  	self setIsRememberedOf: obj2 to: temp2.
  	"swapping headers swaps hash; if !!copyHashFlag undo hash copy"
  	copyHashFlag ifFalse:
  		[temp1 := self rawHashBitsOf: obj1.
  		 self setHashBitsOf: obj1 to: (self rawHashBitsOf: obj2).
  		 self setHashBitsOf: obj2 to: temp1].
  	o1HasYoung := o2HasYoung := false.
  	0 to: (self numSlotsOf: obj1) - 1 do:
  		[:i|
  		temp1 := self fetchPointer: i ofObject: obj1.
  		temp2 := self fetchPointer: i ofObject: obj2.
  		self storePointerUnchecked: i
  			ofObject: obj1
  			withValue: temp2.
  		self storePointerUnchecked: i
  			ofObject: obj2
  			withValue: temp1.
  		(self isYoung: temp2) ifTrue:
  			[o1HasYoung := true].
  		(self isYoung: temp1) ifTrue:
  			[o2HasYoung := true]].
  	(self isOldObject: obj1) ifTrue:
  		[fmt := self formatOf: obj1.
  		 (o1HasYoung and: [(self isPureBitsFormat: fmt) not]) ifTrue:
  			[self possibleRootStoreInto: obj1]].
  	(self isOldObject: obj2) ifTrue:
  		[fmt := self formatOf: obj2.
  		 (o2HasYoung and: [(self isPureBitsFormat: fmt) not]) ifTrue:
  			[self possibleRootStoreInto: obj2]]!

Item was changed:
  ----- Method: SpurMemoryManager>>printInvalidClassTableEntries (in category 'class table') -----
  printInvalidClassTableEntries
  	"Print the objects in the classTable that have bad hashes."
  	<api>
  	self validClassTableRootPages ifFalse:
  		[coInterpreter print: 'class table invalid; cannot print'; cr.
  		 ^self].
  
+ 	self classTableEntriesDo:
+ 		[:classOrNil :i :j| | hash |
+ 		 ((self isForwarded: classOrNil)
+ 		  or: [(hash := self rawHashBitsOf: classOrNil) = 0
+ 		  or: [(self noCheckClassAtIndex: hash) ~= classOrNil]]) ifTrue:
+ 			[coInterpreter
+ 				print: 'entry '; printHex: i * self classTablePageSize + j;
+ 				print: ' oop '; printHex: classOrNil;
+ 				print: ' hash '; printHex: hash; print: ' => '; printHex: (self classAtIndex: hash);
+ 				cr]]!
- 	0 to: numClassTablePages - 1 do:
- 		[:i| | page |
- 		 page := self fetchPointer: i ofObject: hiddenRootsObj.
- 		 0 to: self classTablePageSize - 1 do:
- 			[:j| | classOrNil hash |
- 			classOrNil := self fetchPointer: j ofObject: page.
- 			classOrNil ~= nilObj ifTrue:
- 				[((self isForwarded: classOrNil)
- 				  or: [(hash := self rawHashBitsOf: classOrNil) = 0
- 				  or: [(self noCheckClassAtIndex: hash) ~= classOrNil]]) ifTrue:
- 					[coInterpreter
- 						print: 'entry '; printHex: i * self classTablePageSize + j;
- 						print: ' oop '; printHex: classOrNil;
- 						print: ' hash '; printHex: hash; print: ' => '; printHex: (self classAtIndex: hash);
- 						cr]]]]!

Item was added:
+ ----- Method: SpurMemoryManager>>printInvalidClassTableHashes (in category 'class table') -----
+ printInvalidClassTableHashes
+ 	"Print the entries in the classTable that have invalid hashes."
+ 
+ 	self validClassTableRootPages ifFalse:
+ 		[^false].
+ 
+ 	self classTableEntriesDo:
+ 		[:entry :index| | hash |
+ 		 (self isForwarded: entry)
+ 			ifTrue:
+ 				[coInterpreter printHex: entry; print: ' @ '; printHex: index; print: ' forwarder']
+ 			ifFalse:
+ 				[hash := self rawHashBitsOf: entry.
+ 				 hash = 0
+ 					ifTrue:
+ 						[coInterpreter printHex: entry; print: ' @ '; printHex: index; print: ' no hash']
+ 					ifFalse:
+ 						[(self noCheckClassAtIndex: hash) ~= entry ifTrue:
+ 							[coInterpreter printHex: entry; print: ' @ '; printHex: index; print: ' bad hash: '; printHex: hash]]]]!

Item was added:
+ ----- Method: StackInterpreter>>flushBecommedClassesInMethodCache (in category 'object memory support') -----
+ flushBecommedClassesInMethodCache
+ 	"Flush any entries in the cache which refer to a forwarded (becommed) class."
+ 	0 to: MethodCacheSize - 1 by: MethodCacheEntrySize do:
+ 		[:i | | c s |
+ 		c := methodCache at: i + MethodCacheClass.
+ 		s := methodCache at: i + MethodCacheSelector.
+ 		(c ~= 0 and: [s ~= 0
+ 		 and: [objectMemory isForwarded: (objectMemory classOrNilAtIndex: c)]]) ifTrue:
+ 			[methodCache
+ 				at: i + MethodCacheClass put: 0;
+ 				at: i + MethodCacheSelector put: 0]].
+ 	self flushAtCache!

Item was added:
+ ----- Method: StackInterpreter>>flushBecommedClassesInMethodZone (in category 'object memory support') -----
+ flushBecommedClassesInMethodZone
+ 	"This is just a stub for the CoInterpreter"!

Item was changed:
  ----- Method: StackInterpreter>>postBecomeAction: (in category 'object memory support') -----
  postBecomeAction: theBecomeEffectsFlags
  	"Insulate the stack zone from the effects of a become.
  	 All receivers must be unfollowed for two reasons:
  		1. inst var access is direct with no read barrier
  		2. super sends (always to the receiver) have no class check and so don't trap
  		   for forwarded receivers.
  	 Methods must be unfollowed since bytecode access is direct with no read barrier.
  	 But this only needs to be done if the becomeEffectsFlags indicate that a
  	 CompiledMethod was becommed.
  	 The scheduler state must be followed, but only if the becomeEffectsFlags indicate
  	 that a pointer object was becommed."
  	self followForwardingPointersInStackZone: theBecomeEffectsFlags.
  	theBecomeEffectsFlags ~= 0 ifTrue:
  		[(theBecomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  			[self followForwardedMethodsInMethodCache.
  			 self followForwardedMethodsInMethodZone]. "for CoInterpreter"
+ 		 (theBecomeEffectsFlags anyMask: BecameActiveClassFlag) ifTrue:
+ 			[self flushBecommedClassesInMethodCache.
+ 			 self flushBecommedClassesInMethodZone]. "for CoInterpreter"
  		 self followForwardingPointersInScheduler.
  		 self followForwardingPointersInSpecialObjectsArray.
  		 self followForwardingPointersInProfileState]!

Item was changed:
  VMBasicConstants subclass: #VMSpurObjectRepresentationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BecameActiveClassFlag BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag'
- 	classVariableNames: 'BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!



More information about the Vm-dev mailing list