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

commits at source.squeak.org commits at source.squeak.org
Sun Jan 15 00:32:41 UTC 2023


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

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

Name: VMMaker.oscog.seperateMarking-eem.3313
Author: eem
Time: 14 January 2023, 4:32:20.83271 pm
UUID: d4bb0bb7-8449-47c8-b640-3e0ec5ea90cf
Ancestors: VMMaker.oscog.seperateMarking-WoC.3312

Merge VMMaker.oscog-eem.3287

Fix become on compiled methods (for Spur only).  Tim Rowledge's recent attempt to inboard sources uncovered flaws in become with compiled methods on some jitted platforms (specifically ARMv8 linux, which has a dual mapped code zone).

The main changes in this are to
a) never do in-place become on compiled methods on the jit
b) divorce machine code frames referring to cog methods involved in a become
c) refactor to reduce duplication and overrioding in spurPostBecomeAction:
d) fix bugs in mapping the instructionPointer when method and/or newMethod are becommed

=============== Diff against VMMaker.oscog.seperateMarking-WoC.3312 ===============

Item was changed:
  ----- Method: CoInterpreter>>divorceAFrameIf:in: (in category 'frame access') -----
  divorceAFrameIf: criterion in: aStackPage
  	"Divorce at most one frame in the current page (since the divorce may cause the page to be split)
  	 and answer whether a frame was divorced."
  	<var: #criterion declareC: 'sqInt (*criterion)(char *fp)'>
  	<var: #aStackPage type: #'StackPage *'>
  	| theFP calleeFP theSP theContext |
  
  	theFP := aStackPage headFP.
  	theSP := aStackPage headSP.
  	theSP := theSP + objectMemory wordSize. "theSP points at hottest item on frame's stack"
  
  	[(self perform: criterion with: theFP) ifTrue:
  		[theContext := self ensureFrameIsMarried: theFP SP: theSP.
  		 self externalDivorceFrame: theFP andContext: theContext.
+ 		 theFP = framePointer ifTrue:
+ 			[framePointer := 0].
  		 ^true].
  	 calleeFP := theFP.
  	 theFP := self frameCallerFP: theFP.
  	 theFP ~= 0] whileTrue:
  		["theSP points at stacked hottest item on frame's stack"
  		 theSP := self frameCallerSP: calleeFP].
  
  	^false!

Item was added:
+ ----- Method: CoInterpreter>>ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs (in category 'frame access') -----
+ ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs
+ 	"Map all native pcs to bytecoded pcs in all contexts that have a method with a cog method flagged for become
+ 	 See the comment in primitiveArrayBecome."
+ 	<inline: true>
+ 	objectMemory allObjectsDo:
+ 		[:oop| | methodHeader |
+ 		 (objectMemory isContextNonImm: oop) ifTrue:
+ 			[method := objectMemory followObjField: MethodIndex ofObject: oop.
+ 			 methodHeader := self rawHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: oop).
+ 			 ((self isCogMethodReference: methodHeader)
+ 			  and: [(self cCoerceSimple: methodHeader to: #'CogMethod *') isCMMethodFlaggedForBecome]) ifTrue:
+ 				[self widowOrForceToBytecodePC: oop]]]!

Item was added:
+ ----- Method: CoInterpreter>>flushBecommedClassesInMethodCache (in category 'object memory support') -----
+ flushBecommedClassesInMethodCache
+ 	"Override to also flush linked sends to inavlid classes."
+ 	<option: #SpurObjectMemory>
+ 	super flushBecommedClassesInMethodCache.
+ 	cogit unlinkSendsLinkedForInvalidClasses!

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

Item was changed:
  ----- Method: CoInterpreter>>flushMethodsWithMachineCodePrimitivesAndContinueAnswering: (in category 'primitive support') -----
  flushMethodsWithMachineCodePrimitivesAndContinueAnswering: result
  	"Arrange that any and all cog methods with machine code primitives can be and are discarded.
  	 Hence scan contexts and map their PCs to bytecode PCs if required, and scan frames, divorcing
+ 	 the frames of activations if required.  Then continue execution answering result.  THIS MUST BE
- 	 the frames of activationsif required.  Then continue execution answering result.  THIS MUST BE
  	 INVOKED IN THE CONTEXT OF A PRIMITIVE.  It exists to support vmParameterAt:put:."
  	| activeContext theFrame thePage |
+ 	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForCogMethodWithMachineCodePrim:.
- 	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameWithCogMethod:.
  	self ensureAllContextsWithMethodMachineCodePrimitiveMethodHaveBytecodePCs.
  	cogit unlinkSendsToMethodsSuchThat: #cogMethodHasMachineCodePrim: AndFreeIf: true.
  
+ 	"If the top frame was divorced then continue in the interpreter."
- 	"If flushing led to divorce continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		"pop bogus machine-code instructionPointer, arguments and receiver"
  		 self pop: argumentCount + 2 thenPush: result.
  		 cogit ceInvokeInterpret
  		 "NOTREACHED"].
  	"If not, work out where we are and continue"
  	theFrame := self frameOfMarriedContext: activeContext.
  	thePage := stackPages stackPageFor: theFrame.
  	self assert: thePage headFP = theFrame.
  	self setStackPageAndLimit: thePage.
  	self setStackPointersFromPage: thePage.
  	instructionPointer := self popStack.
  	 self pop: argumentCount + 1 thenPush: result!

Item was removed:
- ----- Method: CoInterpreter>>followForwardedMethodsInMethodZone (in category 'object memory support') -----
- followForwardedMethodsInMethodZone
- 	<inline: true>
- 	cogit followForwardedMethods!

Item was added:
+ ----- Method: CoInterpreter>>insulateFramesAndContextsFromCogMethodsFlaggedForBecome (in category 'object access primitives') -----
+ insulateFramesAndContextsFromCogMethodsFlaggedForBecome
+  	| activeContext |
+ 	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForCogMethodFlaggedForBecome:.
+ 	self popStack. "divorceAllFramesSuchThat: sends ensurePushedInstructionPointer, which is a side-effect we don't want here (but need elsewhere)"
+ 	"Mapping native pcs in contexts whose methods are flagged for become will not ensure that pcs are mapped reliably.
+ 	 Consider this arc: a context on a method that has been jitted exists with a native pc.
+ 	 The method is unjitted to make room for other methods to be jitted.
+ 	 The method is becommed.
+ 	 So the scan is only effective for methods in the jit.  Slowing down become so that a rare
+ 	 case may fail more comprehensibly, when its going to fail anyway, is a waste of effort."
+ 	false ifTrue:
+ 		[self ensureAllContextsWithMachineCodeMethodsFlaggedForBecomeHaveBytecodePCs].
+ 	self assert: (framePointer ~= 0) == (self isStillMarriedContext: activeContext).
+ 	(self isStillMarriedContext: activeContext) ifFalse:
+ 		[objectMemory storePointer: SuspendedContextIndex ofObject: self activeProcess withValue: activeContext]!

Item was added:
+ ----- Method: CoInterpreter>>isMachineCodeFrameForCogMethodFlaggedForBecome: (in category 'object access primitives') -----
+ isMachineCodeFrameForCogMethodFlaggedForBecome: theFP
+ 	<var: #theFP type: #'char *'>
+ 	^(self isMachineCodeFrame: theFP)
+ 	  and: [(self mframeHomeMethod: theFP) isCMMethodFlaggedForBecome]!

Item was added:
+ ----- Method: CoInterpreter>>isMachineCodeFrameForCogMethodWithMachineCodePrim: (in category 'plugin primitive support') -----
+ isMachineCodeFrameForCogMethodWithMachineCodePrim: theFP
+ 	<var: #theFP type: #'char *'>
+ 	^(self isMachineCodeFrame: theFP)
+ 	  and: [cogit cogMethodHasMachineCodePrim: (self mframeHomeMethod: theFP)]!

Item was removed:
- ----- Method: CoInterpreter>>isMachineCodeFrameWithCogMethod: (in category 'plugin primitive support') -----
- isMachineCodeFrameWithCogMethod: theFP
- 	<var: #theFP type: #'char *'>
- 	^(self isMachineCodeFrame: theFP)
- 	  and: [cogit cogMethodHasMachineCodePrim: (self mframeHomeMethod: theFP)]!

Item was removed:
- ----- Method: CoInterpreter>>mapVMRegisters (in category 'object memory support') -----
- mapVMRegisters
- 	"Map the oops in the interpreter's vm ``registers'' to their new values 
- 	 during garbage collection or a become: operation."
- 	"Assume: All traced variables contain valid oops.
- 	 N.B. Don't trace messageSelector and lkupClass; these are ephemeral, live
- 	 only during message lookup and because createActualMessageTo will not
- 	 cause a GC these cannot change during message lookup."
- 	<declareTypeForStaticPolymorphism: #SpurStopTheWorldGarbageCollector>
- 	| mapInstructionPointer |
- 	(objectMemory shouldRemapObj: method) ifTrue:
- 		["i.e. interpreter instructionPointer in method as opposed to machine code?"
- 		(mapInstructionPointer := instructionPointer > method) ifTrue:
- 			[instructionPointer := instructionPointer - method]. "*rel to method"
- 		method := objectMemory remapObj: method.
- 		mapInstructionPointer ifTrue:
- 			[instructionPointer := instructionPointer + method]]. "*rel to method"
- 	(objectMemory shouldRemapOop: newMethod) ifTrue: "maybe oop due to object-as-method"
- 		[newMethod := objectMemory remapObj: newMethod]!

Item was changed:
  ----- Method: CoInterpreter>>maybeFixClonedCompiledMethod: (in category 'cog jit support') -----
  maybeFixClonedCompiledMethod: objOop
+ 	"Make sure a cloned method doesn't reference its original's Cog method, if any."
- 	"Make sure a cloned method doesn't reference its originals Cog method, if any."
  	| rawHeader |
  	self assert: (objectMemory isOopCompiledMethod: objOop).
  	rawHeader := self rawHeaderOf: objOop.
  	(self isCogMethodReference: rawHeader) ifTrue:
  		[self
  			rawHeaderOf: objOop
  			put: (self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: CoInterpreter>>postBecomeAction: (in category 'object memory support') -----
  postBecomeAction: theBecomeEffectsFlags
  	"Clear the gcMode var and let the Cogit do its post GC checks."
  	super postBecomeAction: theBecomeEffectsFlags.
  
  	(objectMemory hasSpurMemoryManagerAPI)
+ 		ifTrue: [(theBecomeEffectsFlags anyMask: BecameJittedCompiledMethodFlag) ifTrue:
+ 					[cogit freeBecomeFlaggedMethods].
+ 				cogit followMovableLiteralsAndUpdateYoungReferrers]
- 		ifTrue: [cogit followMovableLiteralsAndUpdateYoungReferrers]
  		ifFalse: [cogit cogitPostGCAction: gcMode].
  	self nilUncoggableMethods.
  	self assert: cogit kosherYoungReferrers.
  	gcMode := 0!

Item was removed:
- ----- Method: CoInterpreter>>preBecomeAction (in category 'object memory support') -----
- preBecomeAction
- 	"Need to set gcMode var (to avoid passing the flag through a lot of the updating code)"
- 	super preBecomeAction.
- 	gcMode := GCModeBecome!

Item was added:
+ ----- Method: CoInterpreter>>preBecomeAction: (in category 'object memory support') -----
+ preBecomeAction: theBecomeEffectsFlags
+ 	super preBecomeAction: theBecomeEffectsFlags.
+ 	"see the comment in InterpreterPrimitives>>primitiveArrayBecome"
+ 	(theBecomeEffectsFlags anyMask: BecameJittedCompiledMethodFlag) ifTrue:
+ 		[self insulateFramesAndContextsFromCogMethodsFlaggedForBecome].
+ 	"Need to set gcMode var (to avoid passing the flag through a lot of the updating code)"
+ 	gcMode := GCModeBecome!

Item was added:
+ ----- Method: CoInterpreter>>primitiveBecomeReturn: (in category 'object access primitives') -----
+ primitiveBecomeReturn: ec
+ 	"Return from a become primitive after invoking become:with:twoWay:copyHash:.
+ 	 If succeeding and the top frame has been divorced then continue in the interpreter.
+ 	 See the comment in primitiveArrayBecome."
+ 
+ 	<inline: false>
+ 	| activeProc activeContextOrNil |
+ 	ec = PrimNoErr
+ 		ifTrue:
+ 			[activeProc := self activeProcess.
+ 			 activeContextOrNil := objectMemory fetchPointer: SuspendedContextIndex ofObject: activeProc.
+ 			 framePointer = 0 ifTrue: "If the top frame was divorced then continue in the interpreter."
+ 				[self assert: (self isContext: activeContextOrNil).
+ 				 self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
+ 				 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContextOrNil.
+ 				 objectMemory
+ 					storePointerUnchecked: SuspendedContextIndex
+ 					ofObject: activeProc
+ 					withValue: objectMemory nilObject.
+ 				"pop bogus machine-code instructionPointer and any primitive arguments"
+ 				 self pop: argumentCount + 1.
+ 				 cogit ceInvokeInterpret
+ 				 "NOTREACHED"].
+ 			"If not, check where we are and continue..."
+ 			activeContextOrNil = objectMemory nilObject ifFalse:
+ 				["divorcing should not have disturbed the topFrame if it wasn;t divorced"
+ 				 self assert: (self isContext: activeContextOrNil).
+ 				 self assert: framePointer = (self frameOfMarriedContext: activeContextOrNil).
+ 				 objectMemory
+ 					storePointerUnchecked: SuspendedContextIndex
+ 					ofObject: activeProc
+ 					withValue: objectMemory nilObject].
+ 			self methodReturnReceiver]
+ 		ifFalse: [self primitiveFailFor: ec]!

Item was changed:
  ----- Method: CoInterpreter>>printPrimLogEntryAt:hasParameter: (in category 'debug support') -----
  printPrimLogEntryAt: i hasParameter: hasParameter
  	<inline: false>
  	"print the entry and answer if it takes a parameter (as the following entry)"
  	| entryOop className length |
  	entryOop := primTraceLog at: i.
  	hasParameter ifTrue:
  		[(objectMemory addressCouldBeObj: entryOop)
  			ifTrue: [className := self nameOfClass: entryOop lengthInto: (self addressOf: length put: [:v| length := v])]
  			ifFalse: [className := 'bad class'. length := 9].
  		 '%.*s\n' f: transcript printf: { length. className }.
  		 ^false].
  	(objectMemory isImmediate: entryOop)
  		ifTrue:
  			[entryOop = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**\n'. ^false].
  			 entryOop = TraceFullGC ifTrue:
  				[self print: '**FullGC**\n'. ^false].
  			 entryOop = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**\n'. ^false].
  			 entryOop = TraceStackOverflow ifTrue:
  				[self print: '**StackOverflow**\n'. ^false].
  			 entryOop = TracePrimitiveFailure ifTrue:
  				[self print: '**PrimitiveFailure** '. ^true].
  			 entryOop = TracePrimitiveRetry ifTrue:
  				[self print: '**PrimitiveRetry**\n'. ^false].
  			 self print: '???\n']
  		ifFalse:
  			[(objectMemory addressCouldBeObj: entryOop)
  				ifFalse: ['%ld!!!!!!\n' f: transcript printf: i]
  				ifTrue:
  					[(objectMemory isCompiledMethod: entryOop)
  						ifTrue:
  							[| methodClass methodSel |
  							 className := '???'. length := 3.
  							 methodClass := self safeMethodClassOf: entryOop.
  							 methodClass ~= objectMemory nilObject ifTrue:
  								[className := self nameOfClass: methodClass lengthInto: (self addressOf: length put: [:v| length := v])].
  							 methodSel := self findSelectorOfMethod: entryOop.
  							 methodSel = objectMemory nilObject
  								ifTrue:
+ 									['%.*s>>(selector not found)\n'
- 									['%.*s>>bad selector %p\n'
  										f: transcript
+ 										printf: { length. className }]
- 										printf: { length. className. methodSel }]
  								ifFalse:
  									['%.*s>>#%.*s\n'
  										f: transcript
  										printf: { length. className.
  												objectMemory numBytesOfBytes: methodSel. objectMemory firstIndexableField: methodSel }]]
  						ifFalse: [objectMemory safePrintStringOf: entryOop. self cr]]].
  	^false!

Item was added:
+ ----- Method: CogBlockMethod>>isCMMethodEtAl (in category 'testing') -----
+ isCMMethodEtAl
+ 	<inline: true>
+ 	^self cmType >= CMMethod!

Item was added:
+ ----- Method: CogBlockMethod>>isCMMethodFlaggedForBecome (in category 'testing') -----
+ isCMMethodFlaggedForBecome
+ 	<inline: true>
+ 	^self cmType = CMMethodFlaggedForBecome!

Item was changed:
  SharedPool subclass: #CogMethodConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMMethodFlaggedForBecome CMOpenPIC CompletePrimitive EncounteredUnknownBytecode InsufficientCodeSpace MaxLiteralCountForCompile MaxMethodSize MaxNegativeErrorCode MaxNumArgs MaxStackCheckOffset MethodTooBig NotFullyInitialized PrimCallCollectsProfileSamples PrimCallIsExternalCall PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod PrimCallOnSmalltalkStack PrimCallOnSmalltalkStackAlign2x ShouldNotJIT UnfailingPrimitive UnimplementedPrimitive YoungSelectorInPIC'
- 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMOpenPIC CompletePrimitive EncounteredUnknownBytecode InsufficientCodeSpace MaxLiteralCountForCompile MaxMethodSize MaxNegativeErrorCode MaxNumArgs MaxStackCheckOffset MethodTooBig NotFullyInitialized PrimCallCollectsProfileSamples PrimCallIsExternalCall PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod PrimCallOnSmalltalkStack PrimCallOnSmalltalkStackAlign2x ShouldNotJIT UnfailingPrimitive UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogMethodSurrogate>>isCMMethodEtAl (in category 'testing') -----
+ isCMMethodEtAl
+ 	^self cmType >= CMMethod!

Item was added:
+ ----- Method: CogMethodSurrogate>>isCMMethodFlaggedForBecome (in category 'testing') -----
+ isCMMethodFlaggedForBecome
+ 	^self cmType = CMMethodFlaggedForBecome!

Item was changed:
  ----- Method: CogMethodSurrogate>>menuPrompt (in category 'breakpoints') -----
  menuPrompt
  	^String streamContents:
  		[:s|
  		 s
  			nextPut: $(;
+ 			nextPutAll: (#(CMFree CMClosedPIC CMOpenPIC CMBlock CMMethod CMMethodFlaggedForBecome)
+ 							detect: [:k| (CogMethodConstants at: k) = self cmType]
+ 							ifNone: [self cmType printString]);
- 			nextPutAll: (#('CMFree ' 'CMMethod' 'CMBlock' 'CMClosedPIC' 'CMOpenPIC') at: self cmType);
  			space;
  			nextPutAll: address hex;
  			space.
+ 		 (self isCMMethodEtAl or: [self isCMClosedPIC or: [self isCMOpenPIC]]) ifTrue:
- 		 (self cmType = CMMethod or: [self cmType = CMClosedPIC or: [self cmType = CMOpenPIC]]) ifTrue:
  			[s nextPutAll: ((cogit objectMemory isBytes: self selector)
  							ifTrue: [cogit coInterpreter stringOf: self selector]
  							ifFalse: [self selector = cogit objectMemory nilObject
  										ifTrue: ['(nil)']
  										ifFalse: [self selector hex]])].
  		 s nextPut: $)]!

Item was changed:
  ----- Method: CogMethodZone>>addToYoungReferrers: (in category 'young referers') -----
+ addToYoungReferrers: writableCogMethod
+ 	<var: #writableCogMethod type: #'CogMethod *'>
+ 	cogit assertValidDualZoneWriteAddress: writableCogMethod.
+ 	self assert: (self occurrencesInYoungReferrers: writableCogMethod) = 0.
+ 	self assert: writableCogMethod cmRefersToYoung.
- addToYoungReferrers: cogMethod
- 	<var: #cogMethod type: #'CogMethod *'>
- 	cogit assertValidDualZoneWriteAddress: cogMethod.
- 	self assert: (self occurrencesInYoungReferrers: cogMethod) = 0.
- 	self assert: cogMethod cmRefersToYoung.
  	self assert: (youngReferrers <= limitAddress
  				and: [youngReferrers >= (limitAddress - (methodCount * objectMemory wordSize))]).
  	(self asserta: limitAddress - (methodCount * objectMemory wordSize) >= mzFreeStart) ifFalse:
  		[self error: 'no room on youngReferrers list'].
  	youngReferrers := youngReferrers - objectMemory wordSize.
  	cogit
  		codeLongAt: youngReferrers
+ 		put: writableCogMethod asUnsignedInteger - cogit getCodeToDataDelta!
- 		put: cogMethod asUnsignedInteger - cogit getCodeToDataDelta!

Item was changed:
  ----- Method: CogMethodZone>>freeMethod: (in category 'compaction') -----
  freeMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  	| writableMethod |
+ 	self deny: cogMethod isCMFree.
- 	self assert: cogMethod cmType ~= CMFree.
  	self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  	cogit ensureWritableCodeZone.
+ 	cogMethod isCMMethodEtAl ifTrue:
+ 		[cogMethod isCMMethodFlaggedForBecome
- 	cogMethod cmType = CMMethod ifTrue:
- 		["For non-Newspeak there should be a one-to-one mapping between bytecoded and
- 		  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
- 		"Only reset the original method's header if it is referring to this CogMethod."
- 		 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
  			ifTrue:
+ 				[NewspeakVM ifTrue:
+ 					[self removeFromUnpairedMethodList: cogMethod]]
- 				[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
- 				 NewspeakVM ifTrue:
- 					[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs > self zoneEnd]) ifTrue:
- 						[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
  			ifFalse:
+ 				["For non-Newspeak there should be a one-to-one mapping between bytecoded and
+ 				  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
+ 				"Only reset the original method's header if it is referring to this CogMethod."
+ 				 (coInterpreter rawHeaderOf: cogMethod methodObject) asInteger = cogMethod asInteger
+ 					ifTrue:
+ 						[coInterpreter rawHeaderOf: cogMethod methodObject put: cogMethod methodHeader.
+ 						 NewspeakVM ifTrue:
+ 							[(objectRepresentation canPinObjects and: [cogMethod nextMethodOrIRCs > self zoneEnd]) ifTrue:
+ 								[objectRepresentation freeIRCs: cogMethod nextMethodOrIRCs]]]
+ 					ifFalse:
+ 						[self cCode: [self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject]
+ 							inSmalltalk: [self assert: ((cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject
+ 													or: [coInterpreter isKindOf: CurrentImageCoInterpreterFacade])].
+ 						 NewspeakVM ifTrue:
+ 							[self removeFromUnpairedMethodList: cogMethod]]].
- 				[self cCode: [self assert: (cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject]
- 					inSmalltalk: [self assert: ((cogit noAssertMethodClassAssociationOf: cogMethod methodObject) = objectMemory nilObject
- 											or: [coInterpreter isKindOf: CurrentImageCoInterpreterFacade])].
- 				 NewspeakVM ifTrue:
- 					[self removeFromUnpairedMethodList: cogMethod]].
  		 cogit maybeFreeCountersOf: cogMethod].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[self removeFromOpenPICList: cogMethod].
  	writableMethod := cogit writableMethodFor: cogMethod.
  	writableMethod cmRefersToYoung: false.
  	writableMethod cmType: CMFree.
  	methodBytesFreedSinceLastCompaction := methodBytesFreedSinceLastCompaction
  												+ cogMethod blockSize!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethodsSummarizing: (in category 'printing') -----
  printCogMethodsSummarizing: summarize
  	<inline: true>
+ 	| cogMethod nm nc no nf nu nb |
- 	| cogMethod nm nc no nf nu |
  	<var: #cogMethod type: #'CogMethod *'>
+ 	nm := nb := nc := no := nf := nu := 0.
- 	nm := nc := no := nf := nu := 0.
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
  		[summarize ifFalse:
  			[coInterpreter printCogMethod: cogMethod].
  		 cogMethod cmType
  			caseOf: {
  			[CMFree]		->	[nf := nf + 1].
  			[CMMethod]	->	[nm := nm + 1].
+ 			[CMMethodFlaggedForBecome]	->	[nb := nb + 1].
  			[CMClosedPIC]	->	[nc := nc + 1].
  			[CMOpenPIC]	->	[no:= no+ 1] }
  			otherwise: [nu := nu + 1].
  		 cogMethod := self methodAfter: cogMethod].
+ 	coInterpreter print: 'CMMethod '; printNum: nm.
+ 	nb > 0 ifTrue:
+ 		[coInterpreter print: ' (flagged for become: '; printNum: nb; print: ')'].
+ 	coInterpreter print: ' CMClosedPIC '; printNum: nc;  print: ' CMOpenPIC '; printNum: no;  print: ' CMFree '; printNum: nf.
- 	coInterpreter print: 'CMMethod '; printNum: nm;  print: ' CMClosedPIC '; printNum: nc;  print: ' CMOpenPIC '; printNum: no;  print: ' CMFree '; printNum: nf.
  	nu > 0 ifTrue:
  		[coInterpreter print: ' UNKNOWN '; printNum: nu].
+ 	coInterpreter print: ' total '; printNum: nm+nc+no+nf+nu+nb; cr!
- 	coInterpreter print: ' total '; printNum: nm+nc+no+nf+nu; cr!

Item was changed:
  ----- Method: Cogit class>>initializeCogMethodConstants (in category 'class initialization') -----
  initializeCogMethodConstants
+ 	CMMethodFlaggedForBecome := 1 + (CMMethod := 1 + (CMBlock := 1 + (CMOpenPIC := 1 + (CMClosedPIC := 1 + (CMFree := 1)))))!
- 	CMOpenPIC := 1 + (CMClosedPIC := 1 + (CMBlock := 1 + (CMMethod := 1 + (CMFree := 1))))!

Item was changed:
+ ----- Method: Cogit>>allMachineCodeObjectReferencesValid (in category 'garbage collection & become') -----
- ----- Method: Cogit>>allMachineCodeObjectReferencesValid (in category 'garbage collection') -----
  allMachineCodeObjectReferencesValid
  	"Check that all methods have valid selectors, and that all linked sends are to valid targets and have valid cache tags"
  	| ok cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	ok := true.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[(self asserta: (objectRepresentation checkValidOopReference: cogMethod selector)) ifFalse:
  				[ok := false].
  			 (self asserta: (self cogMethodDoesntLookKosher: cogMethod) = 0) ifFalse:
  				[ok := false]].
+ 		(cogMethod isCMMethodEtAl
+ 		 or: [cogMethod isCMOpenPIC]) ifTrue:
- 		(cogMethod cmType = CMMethod
- 		 or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  			[(self asserta: ((self mapFor: cogMethod
  								 performUntil: #checkIfValidOopRefAndTarget:pc:cogMethod:
  								 arg: cogMethod) = 0)) ifFalse:
  				[ok := false]].
+ 		(cogMethod isCMMethodEtAl
- 		(cogMethod cmType = CMMethod
  		 and: [(NewspeakVM or: [SistaVM])
  		 and: [objectRepresentation canPinObjects]]) ifTrue:
  			[(SistaVM and: [cogMethod counters ~= 0]) ifTrue:
  				[(self asserta: (objectRepresentation checkValidDerivedObjectReference: cogMethod counters)) ifFalse:
  					[ok := false]].
  			 (NewspeakVM and: [cogMethod nextMethodOrIRCs ~= 0]) ifTrue:
  				[(cogMethod nextMethodOrIRCs > methodZone zoneEnd) ifTrue:
  					[(self asserta: (objectRepresentation checkValidDerivedObjectReference: cogMethod nextMethodOrIRCs)) ifFalse:
  						[ok := false]]]].
+ 		cogMethod isCMClosedPIC ifTrue:
- 		cogMethod cmType = CMClosedPIC ifTrue:
  			[(self asserta: (self noTargetsFreeInClosedPIC: cogMethod)) ifFalse:
  				[ok := false]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	^ok!

Item was changed:
+ ----- Method: Cogit>>allMethodsHaveCorrectHeader (in category 'garbage collection & become') -----
- ----- Method: Cogit>>allMethodsHaveCorrectHeader (in category 'garbage collection') -----
  allMethodsHaveCorrectHeader
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[(objectRepresentation hasValidHeaderPostGC: cogMethod) ifFalse:
  				[^false]].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	^true!

Item was changed:
+ ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
  			^1]].
  
  	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache enclosingObject |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			[(objectRepresentation checkValidOopReference: nsSendCache selector) ifFalse:
  				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
  				^1]].
  			(enclosingObject := nsSendCache enclosingObject) ~= 0 ifTrue:
  				[[(objectRepresentation checkValidOopReference: enclosingObject) ifFalse:
  					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
  					^1]]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
  					into: [:off :table| offset := off]].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
+ 		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') isCMOpenPIC not]])
- 		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation validInlineCacheTag: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
  					^1]]
  			ifFalse: "unlinked send or super send; cacheTag is a selector unless 64-bit, in which case it is an index."
  				[(self inlineCacheTagsAreIndexes
  				  or: [objectRepresentation checkValidOopReference: selectorOrCacheTag]) ifFalse:
  					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; eekcr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
+ ----- Method: Cogit>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  
- 	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal entryPoint |
+ 	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (self asserta: (objectRepresentation checkValidOopReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  
  	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache classTag enclosingObject nsTargetMethod |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(self asserta: (objectRepresentation checkValidOopReference: nsSendCache selector)) ifFalse:
  				[^9].
  			classTag := nsSendCache classTag.
  			(self asserta: (classTag = 0 or: [objectRepresentation validInlineCacheTag: classTag])) ifFalse:
  				[^10].
  			enclosingObject := nsSendCache enclosingObject.
  			(self asserta: (enclosingObject = 0 or: [objectRepresentation checkValidOopReference: enclosingObject])) ifFalse:
  				[^11].
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: [
  				nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				(self asserta: (nsTargetMethod isCMMethodEtAl)) ifFalse:
- 				(self asserta: (nsTargetMethod cmType = CMMethod)) ifFalse:
  					[^12]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
+ 		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') isCMMethodEtAl) ifFalse:
- 		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 self entryCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPt :cacheTag :tagCouldBeObject|
  			entryPoint := entryPt.
  			tagCouldBeObject
  				ifTrue:
  					[(objectRepresentation couldBeObject: cacheTag)
  						ifTrue:
  							[(self asserta: (objectRepresentation checkValidOopReference: cacheTag)) ifFalse:
  								[^4]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^5]].
  					((objectRepresentation couldBeObject: cacheTag)
  					 and: [objectMemory isReallyYoungObject: cacheTag]) ifTrue:
  						[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  							[^6]]]
  				ifFalse:
  					[(self inlineCacheTagsAreIndexes
  					  and: [self entryPointTagIsSelector: entryPoint])
  						ifTrue:
  							[cacheTag signedIntFromLong < 0
  								ifTrue:
  									[cacheTag signedIntFromLong negated > NumSpecialSelectors ifTrue:
  										[^7]]
  								ifFalse:
  									[cacheTag >= (objectMemory literalCountOf: enumeratingCogMethod methodObject) ifTrue:
  										[^8]]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^9]]]].
  		entryPoint > methodZoneBase ifTrue:
  			["It's a linked send; find which kind."
  			 self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable|
+ 					 (self asserta: (targetMethod isCMMethodEtAl
+ 								   or: [targetMethod isCMClosedPIC
+ 								   or: [targetMethod isCMOpenPIC]])) ifFalse:
- 					 (self asserta: (targetMethod cmType = CMMethod
- 								   or: [targetMethod cmType = CMClosedPIC
- 								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^10]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
+ 	"Fill in the header for theCogMethod method.  This may be located at the writable mapping."
- 	"Fill in the header for theCogMehtod method.  This may be located at the writable mapping."
  	<var: #method type: #'CogMethod *'>
  	| originalMethod rawHeader actualMethodLocation |
  	<var: #originalMethod type: #'CogMethod *'>
  	actualMethodLocation := method asUnsignedInteger - codeToDataDelta.
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	rawHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: rawHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			self assert: methodHeader = originalMethod methodHeader.
  			NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: actualMethodLocation.
  			 NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	method cmHasMovableLiteral: hasMovableLiteral.
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - actualMethodLocation]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - actualMethodLocation <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - actualMethodLocation]
  								ifFalse: [0]).
  
  	self assert: (backEnd callTargetFromReturnAddress: actualMethodLocation + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
  	self assertValidDualZoneFrom: actualMethodLocation to: actualMethodLocation + size.
  	self maybeEnableSingleStep!

Item was added:
+ ----- Method: Cogit>>flagCogMethodForBecome: (in category 'garbage collection & become') -----
+ flagCogMethodForBecome: cogMethod
+ 	<api>
+ 	<var: 'cogMethod' type: #'CogMethod *'>
+ 	self assert: cogMethod isCMMethodEtAl.
+ 	self ensureWritableCodeZone.
+ 	(self writableMethodFor: cogMethod) cmType: CMMethodFlaggedForBecome!

Item was changed:
+ ----- Method: Cogit>>followForwardedLiteralsImplementationIn: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>followForwardedLiteralsImplementationIn: (in category 'garbage collection') -----
  followForwardedLiteralsImplementationIn: cogMethod
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
  	| writableCogMethod hasYoungObj hasYoungObjPtr |
+ 	self assert: (cogMethod isCMMethodEtAl not or: [(objectMemory isForwarded: cogMethod methodObject) not]).
- 	self assert: (cogMethod cmType ~= CMMethod or: [(objectMemory isForwarded: cogMethod methodObject) not]).
  	writableCogMethod := self writableMethodFor: cogMethod.
  	hasYoungObj := objectMemory isYoung: cogMethod methodObject.
  	(objectMemory shouldRemapOop: cogMethod selector) ifTrue:
  		[writableCogMethod selector: (objectMemory remapObj: cogMethod selector).
  		 (objectMemory isYoung: cogMethod selector) ifTrue:
  			[hasYoungObj := true]].
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	self mapFor: cogMethod
  		performUntil: #remapIfObjectRef:pc:hasYoung:
  		arg: hasYoungObjPtr asVoidPointer.
  	hasYoungObj
  		ifTrue: [methodZone ensureInYoungReferrers: cogMethod]
  		ifFalse: [writableCogMethod cmRefersToYoung: false]!

Item was changed:
+ ----- Method: Cogit>>followForwardedMethods (in category 'garbage collection & become') -----
- ----- Method: Cogit>>followForwardedMethods (in category 'garbage collection') -----
  followForwardedMethods
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod freedPIC |
  	self ensureWritableCodeZone.
  	freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[(objectMemory isForwarded: cogMethod methodObject) ifTrue:
  				[cogMethod methodObject: (objectMemory followForwarded: cogMethod methodObject).
  				 (objectMemory isYoungObject: cogMethod methodObject) ifTrue:
  					[methodZone ensureInYoungReferrers: cogMethod]]].
+ 		 cogMethod isCMClosedPIC ifTrue:
- 		 cogMethod cmType = CMClosedPIC ifTrue:
  			[(self followMethodReferencesInClosedPIC: cogMethod) ifTrue:
  				[freedPIC := true.
  				 methodZone freeMethod: cogMethod]].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedPIC ifTrue:
  		[self unlinkSendsToFree].
  	self ensureExecutableCodeZone!

Item was changed:
+ ----- Method: Cogit>>followMovableLiteralsAndUpdateYoungReferrers (in category 'garbage collection & become') -----
- ----- Method: Cogit>>followMovableLiteralsAndUpdateYoungReferrers (in category 'garbage collection') -----
  followMovableLiteralsAndUpdateYoungReferrers
  	"To avoid runtime checks on literal variable and literal accesses in == and ~~, 
  	 we follow literals in methods having movable literals in the postBecome action.
  	 To avoid scanning every method, we annotate cogMethods with the 
  	 cmHasMovableLiteral flag."
  	<option: #SpurObjectMemory>
  	<api>
  	<returnTypeC: #void>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: methodZone kosherYoungReferrers.
  	"methodZone firstBogusYoungReferrer"
  	"methodZone occurrencesInYoungReferrers: methodZone firstBogusYoungReferrer"
  	codeModified := false.
  	self ensureWritableCodeZone.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMFree or: [cogMethod isCMMethodFlaggedForBecome]) ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmHasMovableLiteral ifTrue:
  				[self followForwardedLiteralsImplementationIn: cogMethod]].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone freeStart].
  	"And ensure code zone is executable.  May have pruned young referrers..."
  	self ensureExecutableCodeZone!

Item was added:
+ ----- Method: Cogit>>freeBecomeFlaggedMethods (in category 'garbage collection & become') -----
+ freeBecomeFlaggedMethods
+ 	<api>
+ 	"N.B. because becomeEffectFlags indicates whether jitted methods were
+ 	 becommed or not, if this method is called flagged methods exist, will be
+ 	 freed, and so on. So there is no need to check. Just do it."
+ 	| cogMethod |
+ 	self ensureWritableCodeZone.
+ 
+ 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodFlaggedForBecome ifTrue:
+ 			[self freeMethod: cogMethod].
+ 		cogMethod := methodZone methodAfter: cogMethod].
+ 
+ 	self unlinkSendsToFree.
+ 
+ 	self ensureExecutableCodeZone!

Item was changed:
+ ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection & become') -----
- ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod writableCogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
+ 		 cogMethod isCMFree ifFalse:
- 		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 writableCogMethod := self writableMethodFor: cogMethod.
  			 writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector).
+ 			 cogMethod isCMClosedPIC
- 			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
+ 					 cogMethod isCMMethodEtAl ifTrue:
- 					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
  									with: cogMethod cmUsesPenultimateLit
  									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 "For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  							  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  							 "Only reset the method object's header if it is referring to this CogMethod."
  							 (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  								ifTrue:
  									[coInterpreter
  										rawHeaderOf: cogMethod methodObject
  										put: cogMethod methodHeader.
  									 writableCogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod.
  									 coInterpreter
  										rawHeaderOf: remappedMethod
  										put: cogMethod asInteger]
  								ifFalse:
  									[self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
  													= objectMemory nilObject.
  									 writableCogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod]].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[methodZone ensureInYoungReferrers: cogMethod.
  							hasYoungObj := false]
  						ifFalse:
  							[cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"we /must/ prune youngReferrers here because a) the [cogMethod cmRefersToYoung: false]
  	 block could have removed a method and subsequently it could be added back, and b) we
  	 can not tolerate duplicates in the youngReferrers list."  
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone freeStart]!

Item was changed:
+ ----- Method: Cogit>>mapObjectReferencesInMachineCodeForFullGC (in category 'garbage collection & become') -----
- ----- Method: Cogit>>mapObjectReferencesInMachineCodeForFullGC (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForFullGC
  	"Update all references to objects in machine code for a full gc.  Since
  	 the current (New)ObjectMemory GC makes everything old in a full GC
  	 a method not referring to young will not refer to young afterwards"
  	| cogMethod writableCogMethod |
  	codeModified := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 writableCogMethod := self writableMethodFor: cogMethod.
  			 writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector).
+ 			 cogMethod isCMClosedPIC
- 			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[self assert: cogMethod cmRefersToYoung not.
  					 self mapObjectReferencesInClosedPIC: cogMethod]
  				ifFalse:
+ 					[cogMethod isCMMethodEtAl ifTrue:
- 					[cogMethod cmType = CMMethod ifTrue:
  						[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 writableCogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject)].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: 0.
  					 (cogMethod cmRefersToYoung
  					  and: [objectRepresentation allYoungObjectsAgeInFullGC]) ifTrue:
  						[writableCogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone freeStart]!

Item was changed:
+ ----- Method: Cogit>>mapObjectReferencesInMachineCodeForYoungGC (in category 'garbage collection & become') -----
- ----- Method: Cogit>>mapObjectReferencesInMachineCodeForYoungGC (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForYoungGC
  	"Update all references to objects in machine code for either a Spur scavenging gc
  	 or a Squeak V3 incremental GC.  Avoid scanning all code by using the youngReferrers
  	 list.  In a young gc a method referring to young may no longer refer to young, but a
  	 method not referring to young cannot and will not refer to young afterwards."
  	| pointer cogMethod hasYoungObj hasYoungObjPtr zoneIsWritable |
  	codeModified := zoneIsWritable := hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
+ 		 cogMethod isCMFree
- 		 cogMethod cmType = CMFree
  			ifTrue: [self assert: cogMethod cmRefersToYoung not]
  			ifFalse:
  				[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  				 cogMethod cmRefersToYoung ifTrue:
  					[| writableCogMethod |
+ 					 self assert: (cogMethod isCMMethodEtAl
+ 								or: [cogMethod isCMOpenPIC]).
- 					 self assert: (cogMethod cmType = CMMethod
- 								or: [cogMethod cmType = CMOpenPIC]).
  					 zoneIsWritable ifFalse:
  						[self ensureWritableCodeZone.
  						 zoneIsWritable := true].
  					 writableCogMethod := self writableMethodFor: cogMethod.
  					 writableCogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  					 (objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
+ 					 cogMethod isCMMethodEtAl ifTrue:
- 					 cogMethod cmType = CMMethod ifTrue:
  						[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 writableCogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject).
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr asVoidPointer.
  					 hasYoungObj
  						ifTrue: [hasYoungObj := false]
  						ifFalse: [writableCogMethod cmRefersToYoung: false]]].
  		 pointer := pointer + objectMemory wordSize].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart]!

Item was changed:
+ ----- Method: Cogit>>markAndTraceLiteralsIn: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>markAndTraceLiteralsIn: (in category 'garbage collection') -----
  markAndTraceLiteralsIn: cogMethod
  	<option: #SpurObjectMemory>
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
+ 	self assert: ((cogMethod isCMMethodEtAl
- 	self assert: ((cogMethod cmType = CMMethod
  				 and: [objectMemory isMarked: cogMethod methodObject])
+ 				 or: [cogMethod isCMOpenPIC
- 				 or: [cogMethod cmType = CMOpenPIC
  				 and: [(objectMemory isImmediate: cogMethod selector)
  					or: [objectMemory isMarked: cogMethod selector]]]).
  	objectRepresentation
  		markAndTraceLiteral: cogMethod selector
  		in: cogMethod
  		at: (self addressOf: cogMethod selector put: [:val| cogMethod selector: val]).
  	self maybeMarkCountersIn: cogMethod.
  	self maybeMarkIRCsIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiterals:pc:method:
  		 arg: cogMethod!

Item was changed:
+ ----- Method: Cogit>>markAndTraceOrFreeCogMethod:firstVisit: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>markAndTraceOrFreeCogMethod:firstVisit: (in category 'garbage collection') -----
  markAndTraceOrFreeCogMethod: cogMethod firstVisit: firstVisit
  	"Mark and trace objects in the argument and free if it is appropriate.
  	 Answer if the method has been freed.  firstVisit is a hint used to avoid
  	 scanning methods we've already seen.  False positives are fine.
  	 For a CMMethod this
  			frees if the bytecode method isnt marked,
  			marks and traces object literals and selectors,
  			unlinks sends to targets that should be freed.
  	 For a CMClosedPIC this
  			frees if it refers to anything that should be freed or isn't marked.
  	 For a CMOpenPIC this
  			frees if the selector isn't marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false> "this recurses at most one level down"
+ 	cogMethod isCMFree ifTrue:
- 	cogMethod cmType = CMFree ifTrue:
  		[^true].
  	self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isMarked: cogMethod methodObject) ifFalse:
  			[self ensureWritableCodeZone.
  			 methodZone freeMethod: cogMethod.
  			 ^true].
  		 firstVisit ifTrue:
  			[self markLiteralsAndUnlinkUnmarkedSendsIn: cogMethod].
  		^false].
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[(self closedPICRefersToUnmarkedObject: cogMethod) ifFalse:
  			[^false].
  		 self ensureWritableCodeZone.
  		 methodZone freeMethod: cogMethod.
  		 ^true].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[(objectMemory isMarked: cogMethod selector) ifTrue:
  			[^false].
  		 self ensureWritableCodeZone.
  		 methodZone freeMethod: cogMethod.
  		 ^true].
+ 	self assert: (cogMethod isCMMethodEtAl
+ 				or: [cogMethod isCMClosedPIC
+ 				or: [cogMethod isCMOpenPIC]]).
- 	self assert: (cogMethod cmType = CMMethod
- 				or: [cogMethod cmType = CMClosedPIC
- 				or: [cogMethod cmType = CMOpenPIC]]).
  	^false!

Item was changed:
+ ----- Method: Cogit>>markAndTraceOrFreePICTarget:in: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>markAndTraceOrFreePICTarget:in: (in category 'garbage collection') -----
  markAndTraceOrFreePICTarget: entryPoint in: cPIC
  	"If entryPoint is that of some method, then mark and trace objects in it and free if it is appropriate.
  	 Answer if the method has been freed."
  	<var: #cPIC type: #'CogMethod *'>
  	| targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	self assert: (entryPoint > methodZoneBase and: [entryPoint < methodZone freeStart]).
  	(cPIC containsAddress: entryPoint) ifTrue:
  		[^false].
  	targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 	self assert: (targetMethod isCMMethodEtAl or: [targetMethod isCMFree]).
- 	self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
  	^self markAndTraceOrFreeCogMethod: targetMethod
  		  firstVisit: targetMethod asUnsignedInteger > cPIC asUnsignedInteger!

Item was changed:
+ ----- Method: Cogit>>markLiteralsAndUnlinkUnmarkedSendsIn: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>markLiteralsAndUnlinkUnmarkedSendsIn: (in category 'garbage collection') -----
  markLiteralsAndUnlinkUnmarkedSendsIn: cogMethod
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
+ 	self assert: cogMethod isCMMethodEtAl.
- 	self assert: cogMethod cmType = CMMethod.
  	self assert: (objectMemory isMarked: cogMethod methodObject).
  	objectRepresentation
  		markAndTraceLiteral: cogMethod selector
  		in: cogMethod
  		at: (self addressOf: cogMethod selector put: [:val| cogMethod selector: val]).
  	self maybeMarkCountersIn: cogMethod.
  	self maybeMarkIRCsIn: cogMethod.
  	self mapFor: cogMethod
  		 performUntil: #markLiteralsAndUnlinkIfUnmarkedSend:pc:method:
  		 arg: cogMethod!

Item was changed:
+ ----- Method: Cogit>>markYoungObjectsIn: (in category 'garbage collection & become') -----
- ----- Method: Cogit>>markYoungObjectsIn: (in category 'garbage collection') -----
  markYoungObjectsIn: cogMethod
  	"Mark young literals in the method."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
+ 	self assert: (cogMethod isCMMethodEtAl
+ 				or: [cogMethod isCMOpenPIC]).
- 	self assert: (cogMethod cmType = CMMethod
- 				or: [cogMethod cmType = CMOpenPIC]).
  	 (objectMemory isYoung: cogMethod selector) ifTrue:
  		[objectMemory markAndTrace: cogMethod selector].
+ 	(cogMethod isCMMethodEtAl
- 	(cogMethod cmType = CMMethod
  	 and: [objectMemory isYoung: cogMethod methodObject]) ifTrue:
  		[objectMemory markAndTrace: cogMethod methodObject].
  	self mapFor: cogMethod
  		 performUntil: #markYoungObjects:pc:method:
  		 arg: cogMethod!

Item was added:
+ ----- Method: Cogit>>unflagBecomeFlaggedMethods (in category 'garbage collection & become') -----
+ unflagBecomeFlaggedMethods
+ 	<api>
+ 	| cogMethod |
+ 	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ 	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodFlaggedForBecome ifTrue:
+ 			[(self writableMethodFor: cogMethod) cmType: CMMethod].
+ 		cogMethod := methodZone methodAfter: cogMethod]!

Item was added:
+ ----- Method: Cogit>>whereIs: (in category 'debugging') -----
+ whereIs: aValue
+ 	<doNotGenerate>
+ 	^coInterpreter whereIs: aValue!

Item was removed:
- ----- Method: ImageLeakChecker>>preBecomeAction (in category 'no-op overrides') -----
- preBecomeAction!

Item was added:
+ ----- Method: ImageLeakChecker>>preBecomeAction: (in category 'no-op overrides') -----
+ preBecomeAction: theBecomeEffectsFlags!

Item was removed:
- ----- Method: Interpreter class>>wantsLabels (in category 'translation') -----
- wantsLabels
- 	"Only label the VM, not plugins (internal or external).  This to cut down the scope
- 	 of problems with labels being duplicated by C compiler optimizer inlining and
- 	 loop unrolling.  We use the asmLabel: directive to control labelling in the
- 	 interpreter proper. But it is too much work doing that for plugins too."
- 	^true!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveArrayBecome (in category 'object access primitives') -----
  primitiveArrayBecome
+ 	"Invoke the two-way become primitive.
+ 	 We must at least flush the method cache here, to eliminate stale references to mutated classes and/or selectors.
- 	"We must flush the method cache here, to eliminate stale references
- 	to mutated classes and/or selectors."
  
+ 	 If in the CoInterpreter, we must deal with jitted methods being becommed.  In the conception of the abstract VM,
+ 	 unless a CompiledMethod is becommed to one with equivalent bytecode contexts referring to the becommed
+ 	 method will likely fetch invalid bytecodes on resumption. The responsibility for validity here lies with the user of
+ 	 the become primitive, not the VM.  So one could imagine checking for methods becomming equivalent methods
+ 	 and updating Cog methods to refer to their becommed duals.  But that requires machinery to compare two
+ 	 compiled methods to check if their code is equivalent.  A much simpler approach, which also gets the VM to fail
+ 	 in a less confusing place if it is going to fail because the programmer has not ensured compiled code validity
+ 	 across become, is to simply divorce all frames and map context pcs back to bytecode pcs when becomming
+ 	 jitted methods. However, mapping native pcs in contexts whose methods are flagged for become will not ensure
+ 	 that pcs are mapped reliably.  Consider this arc: a context on a method that has been jitted exists with a native pc.
+ 	 The method is unjitted to make room for other methods to be jitted. The method is becommed. So the scan is only
+ 	 effective for methods in the jit.  Slowing down become so that a rare case may fail more comprehensibly, when its
+ 	 going to fail anyway, is a waste of effort.  So we do divorce frames (since machine code frames refer to CogMethods,
+ 	 not methods), but don't scan the entire heap looking for native pcs in contexts. Hence the primitive must be
+ 	 prepared to have its calling frame divorced. We store the context for the top frame in activeProcess.
+ 	 BTW, as of late '22/early '23 this is only done for Spur.
+ 	 See preBecomeAction: and postBecomeAction:"
+ 
  	| arg rcvr ec |
  	arg := self stackTop.
  	rcvr := self stackValue: 1.
  	ec := objectMemory become: rcvr with: arg twoWay: true copyHash: false.
+ 	self primitiveBecomeReturn: ec!
- 	ec = PrimNoErr
- 		ifTrue: [self pop: 1]
- 		ifFalse: [self primitiveFailFor: ec]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWay (in category 'object access primitives') -----
  primitiveArrayBecomeOneWay
+ 	"Invoke the one-way become primitive.
+ 	 See the comment in primitiveArrayBecome for handling pervasive effects on method cacheing and jitting."
- 	"We must flush the method cache here, to eliminate stale references
- 	to mutated classes and/or selectors."
  
  	| arg rcvr ec |
  	arg := self stackTop.
  	rcvr := self stackValue: 1.
  	ec := objectMemory become: rcvr with: arg twoWay: false copyHash: true.
+ 	self primitiveBecomeReturn: ec!
- 	ec = PrimNoErr
- 		ifTrue: [self pop: 1]
- 		ifFalse: [self primitiveFailFor: ec]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayCopyHashArg (in category 'object access primitives') -----
  primitiveArrayBecomeOneWayCopyHashArg
  	"Similar to primitiveArrayBecomeOneWay but accepts a third argument deciding whether to
+ 	 copy the receiver's elements identity hashes over the argument's elements identity hashes.
+ 	 See the comment in primitiveArrayBecome for handling pervasive effects on method cacheing and jitting."
- 	 copy the receiver's elements identity hashes over the argument's elements identity hashes."
  
  	| copyHashFlag ec |
  	self stackTop = objectMemory trueObject
  		ifTrue: [copyHashFlag := true]
  		ifFalse:
  			[self stackTop = objectMemory falseObject
  				ifTrue: [copyHashFlag := false]
  				ifFalse:
  					[self primitiveFailFor: PrimErrBadArgument.
  					 ^nil]].
  	ec := objectMemory
  			become: (self stackValue: 2)
  			with: (self stackValue: 1)
  			twoWay: false
  			copyHash: copyHashFlag.
+ 	self primitiveBecomeReturn: ec!
- 	ec = PrimNoErr
- 		ifTrue: [self pop: argumentCount]
- 		ifFalse: [self primitiveFailFor: ec]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveArrayBecomeOneWayNoCopyHash (in category 'object access primitives') -----
  primitiveArrayBecomeOneWayNoCopyHash
  	"Similar to primitiveArrayBecomeOneWay but does /not/ copy the receiver's
+ 	 elements identity hashes over the argument's elements identity hashes.
+ 	 See the comment in primitiveArrayBecome for handling pervasive effects on method cacheing and jitting."
- 	 elements identity hashes over the argument's elements identity hashes."
  
  	| arg rcvr ec |
  	arg := self stackTop.
  	rcvr := self stackValue: 1.
  	ec := objectMemory become: rcvr with: arg twoWay: false copyHash: false.
+ 	self primitiveBecomeReturn: ec!
- 	ec = PrimNoErr
- 		ifTrue: [self pop: 1]
- 		ifFalse: [self primitiveFailFor: ec]!

Item was added:
+ ----- Method: InterpreterPrimitives>>primitiveBecomeReturn: (in category 'object access primitives') -----
+ primitiveBecomeReturn: ec
+ 	"Return from a become primitive after invoking become:with:twoWay:copyHash:.
+ 	 This is a hook to allow the CoInterpreter to deal with potential divorce of the calling frame.
+ 	 See the comment in primitiveArrayBecome."
+ 
+ 	<inline: #always>
+ 	ec = PrimNoErr
+ 		ifTrue: [self methodReturnReceiver]
+ 		ifFalse: [self primitiveFailFor: ec]!

Item was changed:
  ----- Method: NewObjectMemory>>become:with:twoWay:copyHash: (in category 'become') -----
  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. 
  	Returns PrimNoErr if the primitive succeeds."
  	"Implementation: Uses forwarding blocks to update references as done in compaction."
  	| start |
  	self runLeakCheckerFor: GCModeBecome.
  	(self isArray: array1) ifFalse:
  		[^PrimErrBadReceiver].
  	((self isArray: array2)
  	 and: [(self lastPointerOf: array1) = (self lastPointerOf: array2)]) ifFalse:
  		[^PrimErrBadArgument].
  	(twoWayFlag or: [copyHashFlag])
  		ifTrue: [(self containOnlyOops: array1 and: array2) ifFalse: [^PrimErrInappropriate]]
  		ifFalse: [(self containOnlyOops: array1) ifFalse: [^PrimErrInappropriate]].
  
  	(self prepareForwardingTableForBecoming: array1 with: array2 twoWay: twoWayFlag) ifFalse:
  		[^PrimErrNoMemory]. "fail; not enough space for forwarding table"
  
  	(self allYoung: array1 and: array2)
  		ifTrue: [start := youngStart"sweep only the young objects plus the roots"]
  		ifFalse: [start := self startOfMemory"sweep all objects"].
+ 	coInterpreter preBecomeAction: 0.
- 	coInterpreter preBecomeAction.
  	self mapPointersInObjectsFrom: start to: freeStart.
  	twoWayFlag
  		ifTrue: [self restoreHeadersAfterBecoming: array1 with: array2]
  		ifFalse: [self restoreHeadersAfterForwardBecome: copyHashFlag].
  	coInterpreter postBecomeAction: 0.
  
  	self initializeMemoryFirstFree: freeStart. "re-initialize memory used for forwarding table"
  	self runLeakCheckerFor: GCModeBecome.
  
  	^PrimNoErr "success"!

Item was added:
+ ----- Method: NewObjectMemory>>sizeBitsOfAny: (in category 'object access') -----
+ sizeBitsOfAny: objOop
+ 	"Answer the number of bytes in the given object, including its base header, rounded up to an integral number of words."
+ 	"Note: byte indexable objects need to have low bits subtracted from this size."
+ 	<inline: #always>
+ 	^self sizeBitsOf: objOop!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager class>>initializeSpurObjectRepresentationConstants (in category 'class initialization') -----
+ initializeSpurObjectRepresentationConstants
+ 	"SpurMemoryManager initializeSpurObjectRepresentationConstants"
+ 	super initializeSpurObjectRepresentationConstants.
+ 	BecameJittedCompiledMethodFlag := 16!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>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. Flag jitted methods because these will have to be freed after divorcing
+ 	 frames and mapping native pcs to bytecode pcs in contexts using them.
+ 	 See the comment in InterpreterPrimitives>>#primitiveArrayBecome"
+ 	<inline: false>
+ 	(self isPointersNonImm: objOop) ifTrue:
+ 		[| hash |
+ 		 ((hash := self rawHashBitsOf: objOop) ~= 0
+ 		  and: [(self classAtIndex: hash) = objOop]) ifTrue:
+ 			[^BecamePointerObjectFlag + BecameActiveClassFlag].
+ 		 ^BecamePointerObjectFlag].
+ 	(self isCompiledMethod: objOop) ifTrue:
+ 		[| methodHeader |
+ 		 methodHeader := coInterpreter rawHeaderOf: objOop.
+ 		 (coInterpreter isCogMethodReference: methodHeader) ifTrue:
+ 			[cogit flagCogMethodForBecome: (self cCoerceSimple: methodHeader to: #'CogMethod *').
+ 			 ^BecameCompiledMethodFlag + BecameJittedCompiledMethodFlag].
+ 		^BecameCompiledMethodFlag].
+ 	^0!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>doBecome:and:copyHash: (in category 'become implementation') -----
+ doBecome: obj1 and: obj2 copyHash: copyHashFlag
+ 	"Inner dispatch for two-way become.
+ 	 Override to never do in-place become on CompiledCode objects.
+ 	 N.B. At least in current two-way become use copyHashFlag is false."
+ 	| o1ClassIndex o2ClassIndex |
+ 	"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.
+ 	 Refuse to do an in-place become on compiled code because
+ 	 doing so breaks the unmapping of methods from cog methods."
+ 	((self numSlotsOf: obj1) = (self numSlotsOf: obj2)
+ 	 and: [o1ClassIndex + o2ClassIndex = 0
+ 	 and: [(self isCompiledMethod: obj1) not
+ 	 and: [(self isCompiledMethod: obj2) not]]]) ifTrue:
+ 		[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag.
+ 		 ^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."
+ 	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"
+ 					[| newObj2 |
+ 					 newObj2 := self followForwarded: obj1.
+ 					 self assert: (self rawHashBitsOf: newObj2) = 0.
+ 					 self setHashBitsOf: newObj2 to: o1ClassIndex]]
+ 		ifFalse:
+ 			[o2ClassIndex ~= 0 ifTrue: "o1 wasn't in the table; set its hash"
+ 				[| newObj1 |
+ 				 newObj1 := self followForwarded: obj2.
+ 				 self assert: (self rawHashBitsOf: newObj1) = 0.
+ 				 self setHashBitsOf: newObj1 to: o2ClassIndex]]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>validPostBecomeArrayContents: (in category 'become implementation') -----
+ validPostBecomeArrayContents: anArray
+ 	"Check that all compiled methods in anArray have valid headers; i.e. none are paired with CogMethods."
+ 
+ 	0 to: (self numSlotsOf: anArray) - 1 do:
+ 		[:i| | objOop |
+ 		objOop := self fetchPointer: i ofObject: anArray.
+ 		((self isOopCompiledMethod: objOop)
+ 		and: [coInterpreter methodHasCogMethod: objOop]) ifTrue:
+ 			[^false]].
+ 	^true!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>zeroBecomeEffectFlagsOnFailure (in category 'become implementation') -----
+ zeroBecomeEffectFlagsOnFailure
+ 	"Set becomeEffectsFlags back to zero when containsOnlyValidBecomeObjects:and:twoWay:copyHash: answers failure.
+ 	 Also unflag any jitted methods flagged for become if required."
+ 	<inline: #always>
+ 	(becomeEffectsFlags anyMask: BecameJittedCompiledMethodFlag) ifTrue:
+ 		[cogit unflagBecomeFlaggedMethods].
+ 	becomeEffectsFlags := 0!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>initializeSpurObjectRepresentationConstants (in category 'class initialization') -----
+ initializeSpurObjectRepresentationConstants
+ 	"SpurMemoryManager initializeSpurObjectRepresentationConstants"
+ 	super initializeSpurObjectRepresentationConstants.
+ 	BecameJittedCompiledMethodFlag := 16!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>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. Flag jitted methods because these will have to be freed after divorcing
+ 	 frames and mapping native pcs to bytecode pcs in contexts using them.
+ 	 See the comment in InterpreterPrimitives>>#primitiveArrayBecome"
+ 	<inline: false>
+ 	(self isPointersNonImm: objOop) ifTrue:
+ 		[| hash |
+ 		 ((hash := self rawHashBitsOf: objOop) ~= 0
+ 		  and: [(self classAtIndex: hash) = objOop]) ifTrue:
+ 			[^BecamePointerObjectFlag + BecameActiveClassFlag].
+ 		 ^BecamePointerObjectFlag].
+ 	(self isCompiledMethod: objOop) ifTrue:
+ 		[| methodHeader |
+ 		 methodHeader := coInterpreter rawHeaderOf: objOop.
+ 		 (coInterpreter isCogMethodReference: methodHeader) ifTrue:
+ 			[cogit flagCogMethodForBecome: (coInterpreter cCoerceSimple: methodHeader to: #'CogMethod *').
+ 			 ^BecameCompiledMethodFlag + BecameJittedCompiledMethodFlag].
+ 		^BecameCompiledMethodFlag].
+ 	^0!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>doBecome:and:copyHash: (in category 'become implementation') -----
+ doBecome: obj1 and: obj2 copyHash: copyHashFlag
+ 	"Inner dispatch for two-way become.
+ 	 Override to never do in-place become on CompiledCode objects.
+ 	 N.B. At least in current two-way become use copyHashFlag is false."
+ 	| o1Header o2Header o1ClassIndex o2ClassIndex |
+ 	"in-lined
+ 			classIndex := (self isInClassTable: obj) ifTrue: [self rawHashBitsOf: obj] ifFalse: [0]
+ 	 for speed."
+ 	o1Header := self baseHeader: obj1.
+ 	o1ClassIndex := self rawHashBitsOfHeader: obj1.
+ 	(o1ClassIndex ~= 0 and: [(self classAtIndex: o1ClassIndex) ~= obj1]) ifTrue:
+ 		[o1ClassIndex := 0].
+ 	o2Header := self baseHeader: obj2.
+ 	o2ClassIndex := self rawHashBitsOfHeader: 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.
+ 	 Refuse to do an in-place become on compiled code because
+ 	 doing so breaks the unmapping of methods from cog methods."
+ 	((self numSlotsOf: obj1) = (self numSlotsOf: obj2)
+ 	 and: [o1ClassIndex + o2ClassIndex = 0
+ 	 and: [(self isCompiledMethodFormat: (self formatOfHeader: o1Header)) not
+ 	 and: [(self isCompiledMethodFormat: (self formatOfHeader: o2Header)) not]]]) ifTrue:
+ 		[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag.
+ 		 ^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."
+ 	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"
+ 					[| newObj2 |
+ 					 newObj2 := self followForwarded: obj1.
+ 					 self assert: (self rawHashBitsOf: newObj2) = 0.
+ 					 self setHashBitsOf: newObj2 to: o1ClassIndex]]
+ 		ifFalse:
+ 			[o2ClassIndex ~= 0 ifTrue: "o1 wasn't in the table; set its hash"
+ 				[| newObj1 |
+ 				 newObj1 := self followForwarded: obj2.
+ 				 self assert: (self rawHashBitsOf: newObj1) = 0.
+ 				 self setHashBitsOf: newObj1 to: o2ClassIndex]]!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager>>zeroBecomeEffectFlagsOnFailure (in category 'become implementation') -----
+ zeroBecomeEffectFlagsOnFailure
+ 	"Set becomeEffectsFlags back to zero when containsOnlyValidBecomeObjects:and:twoWay:copyHash: answers failure.
+ 	 Also unflag any jitted methods flagged for become if required."
+ 	<inline: #always>
+ 	(becomeEffectsFlags anyMask: BecameJittedCompiledMethodFlag) ifTrue:
+ 		[cogit unflagBecomeFlaggedMethods].
+ 	becomeEffectsFlags := 0!

Item was changed:
  ----- Method: SpurMemoryManager>>allInstancesOf: (in category 'primitive support') -----
  allInstancesOf: aClass
  	"Attempt to answer an array of all objects, excluding those that may
  	 be garbage collected as a side effect of allocating the result array.
  	 If no memory is available answer the number of instances as a SmallInteger.
  	 Since objects are at least 16 bytes big, and the largest SmallInteger covers
  	 1/4 of the address space, the count can never overflow."
  	| classIndex freeChunk ptr start limit count bytes |
  	classIndex := self rawHashBitsOf: aClass.
  	classIndex = 0 ifTrue:
  		[freeChunk := self allocateSlots: 0 format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 ^freeChunk].
  	gc markObjectsForEnumerationPrimitives ifTrue:
  		[gc finishGCPass.
  		gc markObjectsCompletely]. "may not want to revive objects unnecessarily; but marking is sloooow."
  	freeChunk := self allocateLargestFreeChunk. "N.B. Does /not/ update totalFreeOldSpace"
  	start := freeChunk + self baseHeaderSize.
  	limit := self addressAfter: freeChunk.
  	(self isClassAtUniqueIndex: aClass)
  		ifTrue:
  			[self uniqueIndex: classIndex allInstancesInto: start limit: limit resultsInto: [:c :p| count := c. ptr := p]]
  		ifFalse:
  			[self ambiguousClass: aClass allInstancesInto: start limit: limit resultsInto: [:c :p| count := c. ptr := p]].
  	self assert: (self isEmptyObjStack: markStack).
  	gc markObjectsForEnumerationPrimitives
  		ifTrue:
  			[self assert: self allObjectsUnmarked.
  			 self emptyObjStack: weaklingStack]
  		ifFalse:
  			[self assert: (self isEmptyObjStack: weaklingStack)].
  	(count > (ptr - start / self bytesPerOop) "not enough room"
  	 or: [limit ~= ptr and: [limit - ptr <= self allocationUnit]]) ifTrue: "can't split a single word"
+ 		[self freeChunkWithBytes: (self bytesInBody: freeChunk) at: (self startOfObject: freeChunk). "N.B. Does /not/ update totalFreeOldSpace"
+ 		 self checkFreeSpace: GCModeFull.
- 		[self freeObject: freeChunk.
  		 ^self integerObjectOf: count].
  	count < self numSlotsMask ifTrue:
  		[| smallObj |
  		 smallObj := self allocateSlots: count format: self arrayFormat classIndex: ClassArrayCompactIndex.
  		 0 to: count - 1 do:
  			[:i|
  			self storePointerUnchecked: i ofObject: smallObj withValue: (self fetchPointer: i ofFreeChunk: freeChunk)].
+ 		 self freeChunkWithBytes: (self bytesInBody: freeChunk) at: (self startOfObject: freeChunk). "N.B. Does /not/ update totalFreeOldSpace"
- 		 self freeChunkWithBytes: (self bytesInBody: freeChunk) at: (self startOfObject: freeChunk).
  		 self beRootIfOld: smallObj.
  		 self checkFreeSpace: GCModeFull.
  		 ^smallObj].
  	bytes := self largeObjectBytesForSlots: count.
  	start := self startOfObject: freeChunk.
  	self freeChunkWithBytes: limit - start - bytes at: start + bytes.
  	totalFreeOldSpace := totalFreeOldSpace - bytes.
  	self rawOverflowSlotsOf: freeChunk put: count.
  	self set: freeChunk classIndexTo: ClassArrayCompactIndex formatTo: self arrayFormat.
  	gc maybeModifyGCFlagsOf: freeChunk.
  	self possibleRootStoreInto: freeChunk.
  	self checkFreeSpace: GCModeFull.
  	self runLeakCheckerFor: GCModeFull excludeUnmarkedObjs: true classIndicesShouldBeValid: true.
  	coInterpreter cr; print: 'allinstances in:  '; printHex: freeChunk; tab; flush.
  	^freeChunk!

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."
  	<inline: false>
  	| ec |
  	self assert: becomeEffectsFlags = 0.
  	self runLeakCheckerFor: GCModeBecome.
  	(self isArray: array1) ifFalse:
  		[^PrimErrBadReceiver].
  	((self isArray: array2)
  	 and: [(self numSlotsOf: array1) = (self numSlotsOf: array2)]) ifFalse:
  		[^PrimErrBadArgument].
  	ec := self containsOnlyValidBecomeObjects: array1 and: array2 twoWay: twoWayFlag copyHash: copyHashFlag.
  	ec ~= 0 ifTrue:
+ 		[self zeroBecomeEffectFlagsOnFailure.
- 		[becomeEffectsFlags := 0.
  		 ^ec].
  
+ 	coInterpreter preBecomeAction: becomeEffectsFlags.
- 	coInterpreter preBecomeAction.
  	twoWayFlag
+ 		ifTrue: [self innerBecomeObjectsIn: array1 and: array2 copyHash: copyHashFlag]
+ 		ifFalse: [self innerBecomeObjectsIn: array1 to: array2 copyHash: copyHashFlag].
- 		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."
  	coInterpreter postBecomeAction: becomeEffectsFlags.
  	self postBecomeScanClassTable: becomeEffectsFlags.
- 	becomeEffectsFlags := 0.
  
+ 	twoWayFlag
+ 		ifTrue:
+ 			[self assert: (self validPostBecomeArrayContents: array1).
+ 			 self assert: (self validPostBecomeArrayContents: array2)]
+ 		ifFalse:
+ 			[self assert: (self validPostBecomeArrayContents: array2)].
+ 
  	self assert: self validClassTableHashes.
  	self runLeakCheckerFor: GCModeBecome.
  
+ 	self zeroBecomeEffectFlagsOnSuccess.
+ 
  	^PrimNoErr "success"!

Item was changed:
  ----- Method: SpurMemoryManager>>bytesLeft: (in category 'free space') -----
  bytesLeft: includeSwapSpace
  	"Answer the amount of available free space. If includeSwapSpace is true, include
  	 possibly available swap space. If includeSwapSpace is false, include possibly available
  	 physical memory.  N.B. includeSwapSpace is ignored; answer total heap free space
+ 	 minus the reserve available for flushing the stack zone."
- 	 minus the reserve available for flushing the tsack zone."
  	^totalFreeOldSpace
+ 	+ (scavengeThreshold - freeStart)
+ 	- coInterpreter interpreterAllocationReserveBytes max: 0!
- 	+ (scavenger eden limit - freeStart)
- 	+ (scavenger pastSpace limit - pastSpaceStart)
- 	+ (scavenger futureSpace limit - scavenger futureSpace limit)
- 	- coInterpreter interpreterAllocationReserveBytes!

Item was changed:
  ----- Method: SpurMemoryManager>>containsOnlyValidBecomeObjects:and:twoWay:copyHash: (in category 'become implementation') -----
  containsOnlyValidBecomeObjects: array1 and: array2 twoWay: isTwoWay copyHash: copyHash
  	"Answer 0 if neither array contains an object inappropriate for the become operation.
  	 Otherwise answer an informative error code for the first offending object found:
  		Can't become: immediates => PrimErrInappropriate
  		Shouldn't become pinned objects => PrimErrObjectIsPinned.
  		Shouldn't become immutable objects => PrimErrNoModification.
  		Can't copy hash into immediates => PrimErrInappropriate.
  		Two-way become may require memory to create copies => PrimErrNoMemory.
  	 As a side-effect unforward any forwarders in the two arrays if answering 0."
  	<inline: true>
+ 	| fieldOffset oop1 oop2 size |
- 	| fieldOffset effectsFlags oop1 oop2 size |
  	fieldOffset := self lastPointerOf: array1.
+ 	size := 0.
- 	effectsFlags := size := 0.
  	"array1 is known to be the same size as array2"
  	[fieldOffset >= self baseHeaderSize] whileTrue:
  		[oop1 := self longAt: array1 + fieldOffset.
  		 (self isOopForwarded: oop1) ifTrue:
  			[oop1 := self followForwarded: oop1.
  			 self longAt: array1 + fieldOffset put: oop1].
  		 self ifOopInvalidForBecome: oop1 errorCodeInto: [:errCode| ^errCode].
  		 oop2 := self longAt: array2 + fieldOffset.
  		 (self isOopForwarded: oop2) ifTrue:
  			[oop2 := self followForwarded: oop2.
  			 self longAt: array2 + fieldOffset put: oop2].
  		 oop1 ~= oop2 ifTrue:
  			[isTwoWay
  				ifTrue:
  					[self ifOopInvalidForBecome: oop2 errorCodeInto: [:errCode| ^errCode].
  					 size := size + (self bytesInBody: oop1) + (self bytesInBody: oop2).
+ 					 becomeEffectsFlags := (becomeEffectsFlags
+ 												bitOr: (self becomeEffectFlagsFor: oop1))
+ 												bitOr: (self becomeEffectFlagsFor: oop2)]
- 					 effectsFlags := (effectsFlags
- 										bitOr: (self becomeEffectFlagsFor: oop1))
- 										bitOr: (self becomeEffectFlagsFor: oop2)]
  				ifFalse:
  					[copyHash ifTrue:
  						[(self isImmediate: oop2) ifTrue:
  							[^PrimErrInappropriate].
  						 (self isObjImmutable: oop2) ifTrue:
  							[^PrimErrNoModification]].
+ 					 becomeEffectsFlags := becomeEffectsFlags bitOr: (self becomeEffectFlagsFor: oop1)]].
- 					 effectsFlags := effectsFlags bitOr: (self becomeEffectFlagsFor: oop1)]].
  		 fieldOffset := fieldOffset - self bytesPerOop].
  	size >= (totalFreeOldSpace + (scavengeThreshold - freeStart)) ifTrue:
+ 		[^PrimErrNoMemory halt].
- 		[^PrimErrNoMemory].
- 	"only set flags after checking all args."
- 	becomeEffectsFlags := effectsFlags.
  	^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
  			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 + o2ClassIndex = 0]) ifTrue:
- 	 and: [o1ClassIndex = 0
- 	 and: [o2ClassIndex = 0]]) ifTrue:
  		[self inPlaceBecome: obj1 and: obj2 copyHashFlag: copyHashFlag.
  		 ^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."
  	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"
  					[| newObj2 |
  					 newObj2 := self followForwarded: obj1.
  					 self assert: (self rawHashBitsOf: newObj2) = 0.
  					 self setHashBitsOf: newObj2 to: o1ClassIndex]]
  		ifFalse:
  			[o2ClassIndex ~= 0 ifTrue: "o1 wasn't in the table; set its hash"
  				[| newObj1 |
  				 newObj1 := self followForwarded: obj2.
  				 self assert: (self rawHashBitsOf: newObj1) = 0.
  				 self setHashBitsOf: newObj1 to: o2ClassIndex]]!

Item was changed:
  ----- Method: SpurMemoryManager>>enterIntoClassTable: (in category 'class table') -----
  enterIntoClassTable: aBehavior
  	"Enter aBehavior into the class table and answer 0.  Otherwise answer a primitive failure code."
  	<inline: false>
  	| initialMajorIndex majorIndex minorIndex page |
  	majorIndex := classTableIndex >> self classTableMajorIndexShift.
  	initialMajorIndex := majorIndex.
  	"classTableIndex should never index the first page; it's reserved for known classes"
  	self assert: initialMajorIndex > 0.
  	minorIndex := classTableIndex bitAnd: self classTableMinorIndexMask.
  
  	[page := self fetchPointer: majorIndex ofObject: hiddenRootsObj.
  	 page = nilObj ifTrue:
  		[page := self allocateSlotsInOldSpace: self classTablePageSize
  					format: self arrayFormat
  					classIndex: self arrayClassIndexPun.
  		 page ifNil:
+ 			[^PrimErrNoMemory halt].
- 			[^PrimErrNoMemory].
  		 self fillObj: page numSlots: self classTablePageSize with: nilObj.
  		 self storePointer: majorIndex
  			ofObject: hiddenRootsObj
  			withValue: page.
  		 numClassTablePages := numClassTablePages + 1.
  		 minorIndex := 0].
  	 minorIndex to: self classTablePageSize - 1 do:
  		[:i|
  		(self fetchPointer: i ofObject: page) = nilObj ifTrue:
  			[classTableIndex := majorIndex << self classTableMajorIndexShift + i.
  			 "classTableIndex must never index the first page, which is reserved for classes known to the VM."
  			 self assert: classTableIndex >= (1 << self classTableMajorIndexShift).
  			 self storePointer: i
  				ofObject: page
  				withValue: aBehavior.
  			 self setHashBitsOf: aBehavior to: classTableIndex.
  			 self assert: (self classAtIndex: (self rawHashBitsOf: aBehavior)) = aBehavior.
  			 ^0]].
  	 majorIndex := (majorIndex + 1 bitAnd: self classIndexMask) max: 1.
  	 majorIndex = initialMajorIndex ifTrue: "wrapped; table full"
  		[^PrimErrLimitExceeded]] repeat!

Item was added:
+ ----- Method: SpurMemoryManager>>rawHashBitsOfHeader: (in category 'header access') -----
+ rawHashBitsOfHeader: header
+ 	<var: 'header' type: #usqLong>
+ 	^header >> self identityHashFullWordShift bitAnd: self identityHashHalfWordMask!

Item was added:
+ ----- Method: SpurMemoryManager>>sizeBitsOfAny: (in category 'object access') -----
+ sizeBitsOfAny: objOop
+ 	"Answer the number of bytes in the given object, including its base header, rounded up to an integral number of words.
+ 	 Unlike sizeBitsOf:, accept forwarded objects."
+ 	"Note: byte indexable objects need to have low bits subtracted from this size to find the address beyond the last byte."
+ 	^(self numSlotsOfAny: objOop) << self shiftForWord + self baseHeaderSize!

Item was changed:
  ----- Method: SpurMemoryManager>>storeImageSegmentInto:outPointers:roots: (in category 'image segment in/out') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: SpurMemoryManager>>validPostBecomeArrayContents: (in category 'become implementation') -----
+ validPostBecomeArrayContents: anArray
+ 	"This is a hook for the CoMemoryManagers to check for valid compiled code.
+ 	 It is a noop here."
+ 
+ 	^true!

Item was added:
+ ----- Method: SpurMemoryManager>>zeroBecomeEffectFlagsOnFailure (in category 'become implementation') -----
+ zeroBecomeEffectFlagsOnFailure
+ 	"Set becomeEffectsFlags back to zero when containsOnlyValidBecomeObjects:and:twoWay:copyHash: answers failure.
+ 	 This is a hook that allows the CoMemoryManagers to reset cog methods that have been flagged as CMMethodFlaggedForBecome."
+ 	<inline: #always>
+ 	becomeEffectsFlags := 0!

Item was added:
+ ----- Method: SpurMemoryManager>>zeroBecomeEffectFlagsOnSuccess (in category 'become implementation') -----
+ zeroBecomeEffectFlagsOnSuccess
+ 	"Set becomeEffectsFlags back to zero at the end of a become."
+ 	<inline: #always>
+ 	becomeEffectsFlags := 0!

Item was removed:
- ----- Method: StackInterpreter class>>macroBenchmark (in category 'benchmarks') -----
- macroBenchmark  "StackInterpreter macroBenchmark"
- 	| dir |
- 	dir := 'benchmark2.dir'.
- 	(FileDirectory default directoryExists: dir)
- 		ifTrue: [(FileDirectory default directoryNamed: dir) recursiveDeleteContents]
- 		ifFalse: [(FileDirectory default directoryNamed: dir) assureExistence].
- 	([VMMaker
- 			makerFor: StackInterpreter
- 			and: nil
- 			with: #()
- 			to: (FileDirectory default pathFromURI: dir)
- 			platformDir: 'none'
- 			excluding:  (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])]
- 		on: VMMakerException "suppress bleats about non-existent platforms dir"
- 		do: [:ex| ex resume: nil])
- 			generateInterpreterFile.
- 	(FileDirectory default directoryNamed: dir) recursiveDeleteContents; recursiveDelete!

Item was removed:
- ----- Method: StackInterpreter class>>patchInterpGCCPPC: (in category 'translation') -----
- patchInterpGCCPPC: fileName
- 	"Interpreter patchInterpGCCPPC: 'Squeak copy 1'"
- 	"This will patch out the unneccesary range check (a compare
- 	 and branch) in the inner interpreter dispatch loop. for the PPC version of the GCC compiled
- 	version of Squeak under MPW"
- 	"NOTE: You must edit in the Interpeter file name"
- 
- 	| delta f code len remnant i |
- 	delta := 7.
- 	f := FileStream fileNamed: fileName.
- 	f binary.
- 	code := Bitmap new: (len := f size) // 4.
- 	f nextInto: code.
- 	remnant := f next: len - (code size * 4).
- 	i := 0.
- 	["Look for a BCTR instruction"
- 	(i := code indexOf: 16r4E800420 startingAt: i + 1 ifAbsent: [0]) > 0] whileTrue:
- 		["Look for a CMPLWI cr1,rxx,FF, 7 instrs back"
- 	       ((code at: i - delta) bitAnd: 16rFFE0FFFF) = 16r288000FF ifTrue:
- 	       	["Copy dispatch instrs back over the compare"
- 			self inform: 'Patching at ', i hex.
- 			0 to: delta - 2 do: [ :j |
- 				code at: (i - delta) + j put: (code at: (i - delta) + j + 2)]]].
- 	f position: 0; nextPutAll: code; nextPutAll: remnant.
- 	f close!

Item was removed:
- ----- Method: StackInterpreter class>>wantsLabels (in category 'translation') -----
- wantsLabels
- 	"Only label the VM, not plugins (internal or external).  This to cut down the scope
- 	 of problems with labels being duplicated by C compiler optimizer inlining and
- 	 loop unrolling.  We use the asmLabel: directive to control labelling in the
- 	 interpreter proper. But it is too much work doing that for plugins too."
- 	^true!

Item was changed:
  ----- Method: StackInterpreter>>findMethodWithPrimitive:FromContext:UpToContext: (in category 'handler search') -----
  findMethodWithPrimitive: primitive FromContext: senderContext UpToContext: homeContext
  	"See findUnwindThroughContext:.  Alas this is mutually recursive with
  	 findMethodWithPrimitive:FromFP:SP:ThroughContext: instead of iterative.
  	 We're doing the simplest thing that could possibly work.  Niceties can wait."
  	<inline: false>
  	<returnTypeC: #sqInt> "Being mutually-recursive with findMethodWithPrimitive:FromFP:UpToContext: gives the author's type inference algorithm headaches.  Wimp out by declaring the return type."
  	| theContext theMethod |
  	self assert: (senderContext = objectMemory nilObject or: [objectMemory isContext: senderContext]).
  	self assert: (homeContext = objectMemory nilObject or: [objectMemory isContext: homeContext]).
  	theContext := senderContext.
  	[theContext = objectMemory nilObject ifTrue:
  		[^theContext].
  	 self isMarriedOrWidowedContext: theContext] whileFalse:
  		[theContext = homeContext ifTrue: [^0].
  		 (primitive = 0
  		  or: [(objectMemory fetchPointer: ClosureIndex ofObject: theContext) ~= objectMemory nilObject]) ifFalse:
+ 		 	[theMethod := objectMemory followObjField: MethodIndex ofObject: theContext.
- 		 	[theMethod := objectMemory fetchPointer: MethodIndex ofObject: theContext.
  			 (self primitiveIndexOf: theMethod) = primitive ifTrue:
  				[^theContext]].
+ 		 theContext := objectMemory followObjField: SenderIndex ofObject: theContext].
- 		 theContext := objectMemory fetchPointer: SenderIndex ofObject: theContext].
  	(self isWidowedContext: theContext) ifTrue:
  		[^objectMemory nilObject].
  	^self
  		findMethodWithPrimitive: primitive
  		FromFP: (self frameOfMarriedContext: theContext)
  		UpToContext: homeContext!

Item was changed:
  ----- Method: StackInterpreter>>findSelectorOfMethod: (in category 'debug support') -----
  findSelectorOfMethod: meth
  	| classObj classDict classDictSize methodArray i |
  	(objectMemory addressCouldBeObj: meth) ifFalse:
  		[^objectMemory nilObject].
  	(objectMemory isForwarded: meth) ifTrue:
  		[^self findSelectorOfMethod: (objectMemory followForwarded: meth)].
  	 (objectMemory isOopCompiledMethod: meth) ifFalse:
  		[^objectMemory nilObject].
  	(self maybeSelectorOfMethod: meth) ifNotNil:
  		[:selector| ^selector].
  	classObj := self safeMethodClassOf: meth.
  	(self addressCouldBeClassObj: classObj) ifTrue:
+ 		[classDict := objectMemory noFixupFollowField: MethodDictionaryIndex ofObject: classObj.
- 		[classDict := objectMemory fetchPointer: MethodDictionaryIndex ofObject: classObj.
  		 classDictSize := objectMemory numSlotsOf: classDict.
  		 classDictSize > MethodArrayIndex ifTrue:
+ 			[methodArray := objectMemory noFixupFollowField: MethodArrayIndex ofObject: classDict.
- 			[methodArray := objectMemory fetchPointer: MethodArrayIndex ofObject: classDict.
  			 i := 0.
  			 [i < (classDictSize - SelectorStart)] whileTrue:
+ 				[meth = (objectMemory noFixupFollowField: i ofObject: methodArray) ifTrue:
+ 					[^(objectMemory noFixupFollowField: i + SelectorStart ofObject: classDict)].
- 				[meth = (objectMemory fetchPointer: i ofObject: methodArray) ifTrue:
- 					[^(objectMemory fetchPointer: i + SelectorStart ofObject: classDict)].
  					 i := i + 1]]].
  	^objectMemory nilObject!

Item was changed:
  ----- Method: StackInterpreter>>flushBecommedClassesInMethodCache (in category 'object memory support') -----
  flushBecommedClassesInMethodCache
  	"Flush any entries in the cache which refer to a forwarded (becommed) class."
+ 	<option: #SpurObjectMemory>
  	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]]!
- 				at: i + MethodCacheSelector put: 0]].
- 	self flushAtCache!

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

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

Item was added:
+ ----- Method: StackInterpreter>>followMethodNewMethodAndInstructionPointer (in category 'object memory support') -----
+ followMethodNewMethodAndInstructionPointer
+ 	"c.f. mapVMRegisters"
+ 	<inline: #always>
+ 	| ipdelta |
+ 	(objectMemory isForwarded: method) ifTrue:
+ 		[ipdelta := (self method: method includesAddress: instructionPointer) ifTrue:
+ 						[instructionPointer - method].
+ 		 method := objectMemory followForwarded: method.
+ 		 ipdelta ifNotNil:
+ 			[instructionPointer := method + ipdelta]].
+ 	(objectMemory isOopForwarded: newMethod) ifTrue:
+ 		[ipdelta := (self method: newMethod includesAddress: instructionPointer) ifTrue:
+ 						[instructionPointer - newMethod].
+ 		 newMethod := objectMemory followForwarded: newMethod].
+ 		 ipdelta ifNotNil:
+ 			[instructionPointer := newMethod + ipdelta]!

Item was changed:
  ----- Method: StackInterpreter>>mapVMRegisters (in category 'object memory support') -----
  mapVMRegisters
  	"Map the oops in the interpreter's vm ``registers'' to their new values 
  	during garbage collection or a become: operation."
  	"Assume: All traced variables contain valid oops.
  	 N.B. Don't trace messageSelector and lkupClass; these are ephemeral, live
  	 only during message lookup and because createActualMessageTo will not
+ 	 cause a GC these cannot change during message lookup.
+ 	 c.f. followMethodNewMethodAndInstructionPointer"
+ 	| ipdelta |
- 	 cause a GC these cannot change during message lookup."
  	(objectMemory shouldRemapObj: method) ifTrue:
+ 		[ipdelta := (self method: method includesAddress: instructionPointer) ifTrue:
+ 						[instructionPointer - method].
- 		[instructionPointer := instructionPointer - method. "*rel to method"
  		 method := objectMemory remapObj: method.
+ 		 ipdelta ifNotNil:
+ 			[instructionPointer := method + ipdelta]].
- 		 instructionPointer := instructionPointer + method]. "*rel to method"
  	(objectMemory shouldRemapOop: newMethod) ifTrue: "maybe oop due to object-as-method"
+ 		[ipdelta := (self method: newMethod includesAddress: instructionPointer) ifTrue:
+ 						[instructionPointer - newMethod].
+ 		 newMethod := objectMemory remapObj: newMethod.
+ 		 ipdelta ifNotNil:
+ 			[instructionPointer := newMethod + ipdelta]]!
- 		[newMethod := objectMemory remapObj: newMethod]!

Item was added:
+ ----- Method: StackInterpreter>>method:includesAddress: (in category 'utilities') -----
+ method: aMethodAddress includesAddress: anAddress
+ 	"Used to test for instructionPointer being within method and/or newMethod, which are all usqInt.
+ 	 N.B. Not reliable to use on sqInt typed variables!!!!"
+ 	<inline: #always>
+ 	^(anAddress > aMethodAddress and: [anAddress < (aMethodAddress + (objectMemory sizeBitsOfAny: aMethodAddress))])!

Item was removed:
- ----- Method: StackInterpreter>>preBecomeAction (in category 'object memory support') -----
- preBecomeAction
- 	"Need to write back the frame pointers unless all pages are free (as in snapshot)"
- 	stackPage ifNotNil:
- 		[self externalWriteBackHeadFramePointers]!

Item was added:
+ ----- Method: StackInterpreter>>preBecomeAction: (in category 'object memory support') -----
+ preBecomeAction: theBecomeEffectsFlags
+ 	"Need to write back the frame pointers unless all pages are free (as in snapshot)"
+ 	stackPage ifNotNil:
+ 		[self externalWriteBackHeadFramePointers]!

Item was removed:
- ----- Method: StackInterpreterSimulator>>preBecomeAction (in category 'object memory support') -----
- preBecomeAction
- 	"((objectMemory instVarNamed: 'becomeEffectsFlags') anyMask: BecameCompiledMethodFlag) ifTrue:
- 		[self halt]."
- 	super preBecomeAction!

Item was changed:
  VMObjectProxy subclass: #VMCompiledMethodProxy
  	instanceVariableNames: 'size numLiterals literals'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMObjectIndices'
- 	poolDictionaries: ''
  	category: 'VMMaker-Support'!
  
  !VMCompiledMethodProxy commentStamp: 'eem 8/6/2014 14:48' prior: 0!
  A VMCompiledMethodProxy is a wrapper for the oop of a CompiledMethod object in the simulator VM's heap that provides accessd to the oop as if it were a CompiledMethod object.!

Item was added:
+ ----- Method: VMCompiledMethodProxy>>methodClass (in category 'accessing') -----
+ methodClass
+ 	"Answer the methodClass oop or nil."
+ 	| methodClassAssociation |
+ 	methodClassAssociation := coInterpreter methodClassAssociationOf: oop.
+ 	^((objectMemory isPointers: methodClassAssociation)
+ 	  and: [(objectMemory numSlotsOf: methodClassAssociation) > ValueIndex]) ifTrue:
+ 		[objectMemory fetchPointer: ValueIndex ofObject: methodClassAssociation]!

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



More information about the Vm-dev mailing list