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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 31 03:54:40 UTC 2022


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

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

Name: VMMaker.oscog-eem.3286
Author: eem
Time: 30 December 2022, 7:54:18.873149 pm
UUID: bc67e1a0-3cc3-4570-82f4-bddf2380be98
Ancestors: VMMaker.oscog-mt.3285

Hide access to CogBlockMethod cmType behind accessors, so as to allow CMMethod to be extended to address an issue with become in an elegant way.

=============== Diff against VMMaker.oscog-mt.3285 ===============

Item was changed:
  ----- Method: CoInterpreter>>asCogHomeMethod: (in category 'frame access') -----
  asCogHomeMethod: aCogMethod
  	"Coerce either a CMMethod or a CMBlock to the home CMMethod"
  	<var: #aCogMethod type: #'CogBlockMethod *'>
  	<returnTypeC: #'CogMethod *'>
+ 	^aCogMethod isCMMethodEtAl
- 	^aCogMethod cmType = CMMethod
  		ifTrue: [self cCoerceSimple: aCogMethod to: #'CogMethod *']
  		ifFalse: [aCogMethod cmHomeMethod]!

Item was changed:
  ----- Method: CoInterpreter>>backupContext:toBlockingSendTo: (in category 'process primitive support') -----
  backupContext: suspendedContext toBlockingSendTo: conditionVariable
  	"Support for primitiveSuspend.
  	 Assume suspendedContext is that of a process waiting on a condition variable.
  	 Backup the PC of suspendedContext to the send that entered the wait state.
  	 primitiveEnterCriticalSection pushes false for blocked waiters. false must be
  	 replaced by the condition variable."
  
  	"The suspendedContext is in one of six states, hence six cases:
  		1 & 2: single context with bytecode pc or single context with machine code pc
  		3 & 4: married to machine code frame in embedded (v3) block or machine code frame in method/full block
  		5 & 6: married to interpreter frame with saved ip or interpreter frame with pushed pc"
  	| theMethod pc sp theIP theNewIP theFP thePage |
  	self assert: (objectMemory isContext: suspendedContext).
  	theMethod := objectMemory fetchPointer: MethodIndex ofObject: suspendedContext.
  	"cases 1 & 2"
  	(self isSingleContext: suspendedContext) ifTrue:
  		[pc := objectMemory fetchPointer: InstructionPointerIndex ofObject: suspendedContext.
  		 sp := objectMemory fetchPointer: StackPointerIndex ofObject: suspendedContext.
  		 self assert: ((objectMemory isIntegerObject: pc) and: [(objectMemory integerValueOf: pc) ~= 0]).
  		 self assert: ((objectMemory isIntegerObject: sp) and: [(objectMemory integerValueOf: sp) > 0]).
  		 "case 2"
  		 (pc := objectMemory integerValueOf: pc) < 0 ifTrue: "context with machine code pc; must map..."
  			[pc := objectMemory integerValueOf: (self mustMapMachineCodePC: pc context: suspendedContext)].
  		 theIP := theMethod + objectMemory baseHeaderSize + pc - 1.
  		 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  		 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  		 pc := theNewIP - theMethod - objectMemory baseHeaderSize + 1.
  		 objectMemory
  			storePointerUnchecked: InstructionPointerIndex
  			ofObject: suspendedContext
  			withValue: (objectMemory integerObjectOf: pc).
  		 sp := (objectMemory integerValueOf: sp) + ReceiverIndex. "implicitly converts to 0 relative"
  		 self assert: ((objectMemory fetchPointer: sp ofObject: suspendedContext) = objectMemory falseObject
  					or: [(objectMemory fetchPointer: sp ofObject: suspendedContext) = conditionVariable]).
  		 objectMemory storePointer: sp ofObject: suspendedContext withValue: conditionVariable.
  		 ^self].
  	self assert: (self isMarriedOrWidowedContext: suspendedContext).
  	self deny: (self isWidowedContextNoConvert: suspendedContext).
  	theFP := self frameOfMarriedContext: suspendedContext.
  	thePage := stackPages stackPageFor: theFP.
  	self deny: thePage = stackPage.
  	self assert: theFP = thePage headFP.
  	(self isMachineCodeFrame: theFP)
  		ifTrue: "cases 3 & 4"
  			[| mcpc startBcpc cogMethod |
  			 mcpc := stackPages longAt: thePage headSP. "a machine code pc... it must be converted..."
  			 cogMethod := self mframeCogMethod: theFP.
+ 			 cogMethod isCMBlock "case 3"
- 			 cogMethod cmType = CMBlock "case 3"
  				ifTrue: [self assert: (self frameStackedReceiver: theFP numArgs: cogMethod cmNumArgs)
  								= (objectMemory fetchPointer: ClosureIndex ofObject: suspendedContext).
  						startBcpc := self startPCOfClosure: (objectMemory fetchPointer: ClosureIndex ofObject: suspendedContext)]
  				ifFalse: [startBcpc := self startPCOfMethod: theMethod]. "case 4"
  			 theIP := cogit bytecodePCFor: mcpc startBcpc: startBcpc in: cogMethod.
  			 theIP := theIP + theMethod + objectMemory baseHeaderSize.
  			 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  			 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  			 self convertFrame: theFP toInterpreterFrame: theIP - theNewIP]
  		ifFalse: "cases 5&6"
  			[theIP := stackPages longAt: thePage headSP.
  			 theIP = cogit ceReturnToInterpreterPC
  				ifTrue: "case 5"
  					[theIP := (self iframeSavedIP: theFP) + 1. "fetchByte uses pre-increment; must + 1 to point at correct bytecode..."
  					 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  					 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  					 self iframeSavedIP: theFP put: theNewIP - 1] "fetchByte uses pre-increment; must - 1 to fetch correct bytecode..."
  				ifFalse: "case 6"
  					[theIP := theIP + 1. "fetchByte uses pre-increment; must + 1 to point at correct bytecode..."
  					 self assert: (self validInstructionPointer: theIP inMethod: theMethod framePointer: theFP).
  					 theNewIP := self perform: pcPreviousToFunction with: theIP with: theMethod.
  					 self assert: (theNewIP < theIP and: [theIP - theNewIP <= 3]).
  					 stackPages longAt: thePage headSP put: theNewIP - 1]]. "fetchByte uses pre-increment; must - 1 to fetch correct bytecode..."
  	self assert: ((stackPages longAt: thePage headSP + objectMemory wordSize) = objectMemory falseObject
  				or: [(stackPages longAt: thePage headSP + objectMemory wordSize) = conditionVariable]).
  	stackPages longAt: thePage headSP + objectMemory wordSize put: conditionVariable!

Item was changed:
  ----- Method: CoInterpreter>>bytecodePCFor:cogMethod:startBcpc: (in category 'frame access') -----
  bytecodePCFor: theIP cogMethod: cogMethod startBcpc: startBcpc
  	"Answer the mapping of the native pc theIP to a zero-relative bytecode pc.
  	 See contextInstructionPointer:frame: for the explanation."
  	<var: #cogMethod type: #'CogMethod *'>
  	| cogMethodForIP mcpc |
  	<inline: true>
  	<var: #cogMethodForIP type: #'CogBlockMethod *'>
  	self assert: theIP < 0.
  	(theIP signedBitShift: -16) < -1 "See contextInstructionPointer:frame:"
  		ifTrue:
  			[cogMethodForIP := self cCoerceSimple: cogMethod asInteger - ((theIP signedBitShift: -16) * cogit blockAlignment)
  									to: #'CogBlockMethod *'.
+ 			 self assert: cogMethodForIP isCMBlock.
- 			 self assert: cogMethodForIP cmType = CMBlock.
  			 self assert: cogMethodForIP cmHomeMethod = cogMethod.
  			 mcpc := cogMethodForIP asInteger - theIP signedIntFromShort]
  		ifFalse:
  			[cogMethodForIP := self cCoerceSimple: cogMethod to: #'CogBlockMethod *'.
+ 			 self assert: cogMethodForIP isCMMethodEtAl.
- 			 self assert: cogMethodForIP cmType = CMMethod.
  			 mcpc := cogMethod asInteger - theIP.
  			 "map any pcs in primitive code (i.e. return addresses for interpreter primitive calls) to the initial pc"
  			 mcpc asUnsignedInteger < cogMethod stackCheckOffset ifTrue:
  				[^startBcpc]].
  	self assert: (mcpc between: cogMethod asInteger and: cogMethod asInteger + cogMethod blockSize).
  	^cogit bytecodePCFor: mcpc startBcpc: startBcpc in: cogMethodForIP!

Item was changed:
  ----- Method: CoInterpreter>>ceInterpretMethodFromPIC:receiver: (in category 'trampolines') -----
  ceInterpretMethodFromPIC: aMethodObj receiver: rcvr
  	<api>
  	| pic primitiveIndex |
  	<var: #pic type: #'CogMethod *'>
  	"pop off inner return and locate open or closed PIC"
  	pic := self cCoerceSimple: self popStack - cogit interpretOffset to: #'CogMethod *'.
+ 	self assert: (pic isCMOpenPIC or: [pic isCMClosedPIC]).
- 	self assert: (pic cmType = CMOpenPIC or: [pic cmType = CMClosedPIC]).
  	"If found from an open PIC then it must be an uncogged method and, since it's been found
  	 in the method cache, should be cogged if possible.  If found from a closed PIC then at the
  	 time the closed PIC was created the method was uncoggable, either because there was
  	 no space, it had too many literals or it contained an illegal bytecode).  So don't try and cog
  	 it, but subsequently it may have been cogged via another path.  If the method is, or ends up
  	 cogged, jump to machine code, otherwise interpret."
+ 	pic isCMOpenPIC ifTrue:
- 	pic cmType = CMOpenPIC ifTrue:
  		[self assert: (self methodHasCogMethod: aMethodObj) not.
  		 (self methodShouldBeCogged: aMethodObj) ifTrue:
  			[cogit cog: aMethodObj selector: pic selector]].
  	(self methodHasCogMethod: aMethodObj) ifTrue:
  		[self executeCogMethod: (self cogMethodOf: aMethodObj)
  			fromUnlinkedSendWithReceiver: rcvr
  		 "NOTREACHED"].
  	messageSelector := pic selector.
  	newMethod := aMethodObj.
  	primitiveIndex := self primitiveIndexOf: aMethodObj.
  	primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  	argumentCount := pic cmNumArgs.
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  	<api>
  	| cPIC primitiveIndex |
  	<var: #cPIC type: #'CogMethod *'>
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	self assert: (aMethodObj = 0
  				or: [(objectMemory addressCouldBeObj: aMethodObj)
  					and: [objectMemory isOopCompiledMethod: aMethodObj]]).
  	self sendBreakpoint: (objectMemory splObj: SelectorDoesNotUnderstand) receiver: rcvr.
  	cPIC := self cCoerceSimple: self popStack - cogit mnuOffset to: #'CogMethod *'.
+ 	self assert: (cPIC isCMClosedPIC or: [cPIC isCMOpenPIC]).
- 	self assert: (cPIC cmType = CMClosedPIC or: [cPIC cmType = CMOpenPIC]).
  	argumentCount := cPIC cmNumArgs.
  	messageSelector := cPIC selector.
  	aMethodObj ~= 0 ifTrue:
  		[instructionPointer := self popStack.
  		self createActualMessageTo: (objectMemory fetchClassOf: rcvr).
  		(self maybeMethodHasCogMethod: aMethodObj) ifTrue:
  			[self push: instructionPointer.
  			 self executeCogMethod: (self cogMethodOf: aMethodObj)
  				 fromUnlinkedSendWithReceiver: rcvr.
  			 "NOTREACHED"
  			 self assert: false].
  		newMethod := aMethodObj.
  		primitiveIndex := self primitiveIndexOf: aMethodObj.
  		primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  		^self interpretMethodFromMachineCode].
  	"handleMNU:InMachineCodeTo:classForMessage: assumes lkupClass is set, since every other use is
  	 after a lookupMethodNoMNUEtcInClass: call, which sets lkupClass.  Here we must set it manually.
  	 Global variables.  Bah!!"
  	self handleMNU: SelectorDoesNotUnderstand
  		InMachineCodeTo: rcvr
  		classForMessage: (lkupClass := objectMemory fetchClassOf: rcvr).
  	"NOTREACHED"
  	self assert: false!

Item was changed:
  ----- Method: CoInterpreter>>ceSendFromInLineCacheMiss: (in category 'trampolines') -----
  ceSendFromInLineCacheMiss: cogMethodOrPIC
  	"Send from an Open PIC when the first-level method lookup probe has failed,
  	 or to continue when PIC creation has failed (e.g. because we're out of code space),
  	 or when a send has failed due to a forwarded receiver."
  	<api>
  	<var: #cogMethodOrPIC type: #'CogMethod *'>
  	| numArgs rcvr classTag classObj errSelIdx |
  	"self printFrame: stackPage headFP WithSP: stackPage headSP"
  	"self printStringOf: selector"
  	numArgs := cogMethodOrPIC cmNumArgs.
  	rcvr := self stackValue: numArgs + 1. "skip return pc"
  	self assert: (objectMemory addressCouldBeOop: rcvr).
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	argumentCount := numArgs.
  	false ifTrue: "would like to assert this but must also allow for an interpretable method in the cache."
+ 		[self deny: (cogMethodOrPIC isCMOpenPIC
- 		[self deny: (cogMethodOrPIC cmType = CMOpenPIC
  					and: [self newMethodInLookupCacheAt: cogMethodOrPIC selector and: classTag])].
  	(self lookupInMethodCacheSel: cogMethodOrPIC selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: cogMethodOrPIC selector]
  		ifFalse:
  			[(objectMemory isOopForwarded: cogMethodOrPIC selector) ifTrue:
  				[self handleForwardedSelectorFaultFor: cogMethodOrPIC selector.
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc".
  				 ^self ceSendFromInLineCacheMiss: cogMethodOrPIC].
  			 messageSelector := cogMethodOrPIC selector.
  			 classObj := objectMemory classForClassTag: classTag.
  			 (errSelIdx := self lookupOrdinaryNoMNUEtcInClass: classObj) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: classObj.
  				"NOTREACHED"
  				self assert: false]].
  	instructionPointer := self popStack.
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self executeNewMethod.
  		 self assert: false
  		 "NOTREACHED"].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>encodedNativePCOf:cogMethod: (in category 'frame access') -----
  encodedNativePCOf: mcpc cogMethod: cogMethod
  	"Encode the mcpc in cogMethod as a value that can be stashed in a context.
  	 Mapping native pcs to bytecode pcs is quite expensive, requiring a search
  	 through the method map.  We mitigate this cost by deferring mapping until
  	 we really have to, which is when a context's instruction pointer is accessed
  	 by Smalltalk code.  But to defer mapping we have to be able to distinguish
  	 machine code from bytecode pcs, which we do by using negative values for
  	 machine code pcs.
  
  	 As a whorish performance hack we also include the block method offset in
  	 the pc of a block. The least significant 16 bits are the native pc and the most
  	 significant 15 bits are the block start, in block alignment units.  So when
  	 mapping back we can find the start of the block.
  
  	 See mustMapMachineCodePC:context: for the code that does the actual mapping."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	| homeMethod blockOffset |
  	<var: #homeMethod type: #'CogMethod *'>
  	mcpc = cogit ceCannotResumePC ifTrue:
  		[^HasBeenReturnedFromMCPCOop].
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[^objectMemory integerObjectOf: cogMethod asInteger - mcpc].
  	homeMethod := cogMethod cmHomeMethod.
  	blockOffset := homeMethod asInteger - cogMethod asInteger / cogit blockAlignment.
  	^objectMemory integerObjectOf: ((blockOffset bitShift: 16) bitOr: (cogMethod asInteger - mcpc bitAnd: 16rFFFF))!

Item was changed:
  ----- Method: CoInterpreter>>flushExternalPrimitives (in category 'plugin primitive support') -----
  flushExternalPrimitives
  	"Flush the references to external functions from plugin primitives.
  	 Then continue execution answering self.
  	 This will force a reload of those primitives when accessed next. 
  	 Note: We must flush the method cache here also, so that any failed
  	 primitives are looked up again.
  	 Override to ensure that any and all activations of an external method
  	 have a bytecode pc so that if code generation changes (e.g. a primitive
  	 method is used, unloaded, and the reloaded primitive is marked with
  	 the FastCPrimitiveFlag) stale machine code pcs have been eliminated.
  	 THIS MUST BE INVOKED IN THE CONTEXT OF A PRIMITIVE."
  	| activeContext theFrame thePage |
  	activeContext := self divorceAllFramesSuchThat: #isMachineCodeFrameForExternalPrimitiveMethod:.
  	objectMemory allObjectsDo:
  		[:oop|
  		(objectMemory isCompiledMethod: oop)
  			ifTrue:
  				[self flushExternalPrimitiveOf: oop]
  			ifFalse:
  				[(objectMemory isContext: oop) ifTrue:
  					[self mapToBytecodePCIfActivationOfExternalMethod: oop]]].
  	cogit unlinkSendsToMethodsSuchThat: #cogMethodHasExternalPrim: AndFreeIf: true.
  	self flushMethodCache.
  	self flushExternalPrimitiveTable.
  	self cCode: '' inSmalltalk:
+ 		[self assert: (cogit methodZone cogMethodsSelect: [:cogMethod| cogMethod isCMFree not and: [cogit cogMethodHasExternalPrim: cogMethod]]) isEmpty].
- 		[self assert: (cogit methodZone cogMethodsSelect: [:cogMethod| cogMethod cmType > CMFree and: [cogit cogMethodHasExternalPrim: cogMethod]]) isEmpty].
  	"If flushing led to divorce continue in the interpreter."
  	(self isStillMarriedContext: activeContext) ifFalse:
  		[self nilStackPage. "to avoid assert in marryContextInNewStackPageAndInitializeInterpreterRegisters:"
  		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
  		 self popStack. "pop pushed instructionPointer"
  		 self pop: argumentCount.
  		 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!

Item was changed:
  ----- Method: CoInterpreter>>marryFrame:SP:copyTemps: (in category 'frame access') -----
  marryFrame: theFP SP: theSP copyTemps: copyTemps
  	"Marry an unmarried frame.  This means creating a spouse context
  	 initialized with a subset of the frame's state that references the frame.
  	 For the default closure implementation we do not need to copy temps.
  	 Different closure implementations may require temps to be copied.
  
  	 This method is important enough for performance to be worth streamlining.
  
  	Override to set the ``has context'' flag appropriately for both machine code and interpreter frames
  	and to streamline the machine code/interpreter differences.."
  	| theContext methodFieldOrObj closureOrNil rcvr numSlots numArgs numStack numTemps |
  	<inline: true>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: (self frameHasContext: theFP) not.
  	self assert: (self isBaseFrame: theFP) not. "base frames must aready be married for cannotReturn: processing"
  
  	"The SP is expected to be pointing at the last oop on the stack, not at the pc"
  	self assert: (objectMemory addressCouldBeOop: (objectMemory longAt: theSP)).
  
  	"Decide how much of the stack to preserve in widowed contexts.  Preserving too much
  	 state will potentially hold onto garbage.  Holding onto too little may mean that a dead
  	 context isn't informative enough in a debugging situation.  If copyTemps is false (as it
  	 is in the default closure implementation) compromise, retaining only the arguments with
  	 no temporaries.  Note that we still set the stack pointer to its current value, but stack
  	 contents other than the arguments are nil."
  	methodFieldOrObj := self frameMethodField: theFP.
  	methodFieldOrObj asUnsignedInteger < objectMemory startOfMemory "inline (self isMachineCodeFrame: theFP)"
  		ifTrue:
  			[| cogMethod |
  			 stackPages
  				longAt: theFP + FoxMethod
  				put: methodFieldOrObj + MFMethodFlagHasContextFlag.
  			 cogMethod := self cCoerceSimple: (methodFieldOrObj bitAnd: MFMethodMask) to: #'CogMethod *'.
  			 numArgs := cogMethod cmNumArgs.
+ 			 cogMethod isCMMethodEtAl
- 			 cogMethod cmType = CMMethod
  				ifTrue:
  					[closureOrNil := cogMethod cmIsFullBlock
  										ifTrue: [self frameStackedReceiver: theFP numArgs: numArgs]
  										ifFalse: [objectMemory nilObject]]
  				ifFalse:
  					[cogMethod := (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod.
  					 closureOrNil := self frameStackedReceiver: theFP numArgs: numArgs].
  			 numSlots := (self methodHeaderIndicatesLargeFrame: cogMethod methodHeader)
  							ifTrue: [LargeContextSlots]
  							ifFalse: [SmallContextSlots].
  			 methodFieldOrObj := cogMethod methodObject.
  			 rcvr := self mframeReceiver: theFP.
  			 numStack := self stackPointerIndexForMFrame: theFP WithSP: theSP numArgs: numArgs]
  		ifFalse:
  			[self setIFrameHasContext: theFP.
  			 numArgs := self iframeNumArgs: theFP.
  			 numSlots := (self methodHeaderIndicatesLargeFrame: (objectMemory methodHeaderOf: methodFieldOrObj))
  							ifTrue: [LargeContextSlots]
  							ifFalse: [SmallContextSlots].
  			 closureOrNil := (self iframeIsBlockActivation: theFP)
  								ifTrue: [self frameStackedReceiver: theFP numArgs: numArgs]
  								ifFalse: [objectMemory nilObject].
  			 rcvr := self iframeReceiver: theFP.
  			 numStack := self stackPointerIndexForIFrame: theFP WithSP: theSP numArgs: numArgs].
  	theContext := objectMemory eeInstantiateMethodContextSlots: numSlots.
  	self setFrameContext: theFP to: theContext.
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity)"
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: theFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: (self frameCallerFP: theFP)).
  	objectMemory storePointerUnchecked: StackPointerIndex
  		ofObject: theContext
  		withValue: (objectMemory integerObjectOf: numStack).
  	objectMemory storePointerUnchecked: MethodIndex
  		ofObject: theContext
  		withValue: methodFieldOrObj.
  	objectMemory storePointerUnchecked: ClosureIndex ofObject: theContext withValue: closureOrNil.
  	objectMemory storePointerUnchecked: ReceiverIndex
  		ofObject: theContext
  		withValue: rcvr.
  	1 to: numArgs do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: (self temporary: i - 1 in: theFP)].
  	copyTemps ifTrue:
  		[numTemps := self frameNumTemps: theFP.
  		 1 to: numTemps do:
  			[:i|
  			objectMemory storePointerUnchecked: ReceiverIndex + i + numArgs
  				ofObject: theContext
  				withValue: (self temporary: i - 1 in: theFP)].
  		 numArgs := numArgs + numTemps].
  
  	numArgs + 1 to: numStack do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: objectMemory nilObject].
  
  	self assert: (self frameHasContext: theFP).
  	self assert: (self frameOfMarriedContext: theContext) = theFP.
  	self assert: numStack + ReceiverIndex < (objectMemory lengthOf: theContext).
  
  	^theContext!

Item was changed:
  ----- Method: CoInterpreter>>printCogMethod: (in category 'debug printing') -----
  printCogMethod: cogMethod
  	<export: true> "useful for VM debugging; use export: so it will be accessible on win32"
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| address primitive |
  	self cCode: ''
  		inSmalltalk:
  			[transcript ensureCr.
  			 cogMethod isInteger ifTrue:
  				[^self printCogMethod: (self cCoerceSimple: cogMethod to: #'CogMethod *')]].
  	address := cogMethod asInteger.
  	self printHex: address;
  		print: ' <-> ';
  		printHex: address + cogMethod blockSize.
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[self print: ': method: ';
  			printHex: cogMethod methodObject.
  		 primitive := self primitiveIndexOfMethod: cogMethod methodObject
  							header: cogMethod methodHeader.
  		 primitive ~= 0 ifTrue:
  			[self print: ' prim '; printNum: primitive].
  		 (objectMemory addressCouldBeObj: cogMethod methodObject) ifTrue:
  			 [cogMethod cmIsFullBlock
  				ifTrue: [self print: ' [full]']
  				ifFalse:
  					[(objectMemory addressCouldBeObj: (self methodClassOf: cogMethod methodObject)) ifTrue:
  						[self space; printNameOfClass: (self methodClassOf: cogMethod methodObject) count: 2]]]].
+ 	cogMethod isCMBlock ifTrue:
- 	cogMethod cmType = CMBlock ifTrue:
  		[self print: ': block home: ';
  			printHex: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod asUnsignedInteger].
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[self print: ': Closed PIC N: ';
  			printHex: cogMethod cPICNumCases].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[self print: ': Open PIC '].
  	self print: ' selector: '; printHex: cogMethod selector.
  	cogMethod selector = objectMemory nilObject
  		ifTrue: [| s |
+ 			(cogMethod isCMMethodEtAl
- 			(cogMethod cmType = CMMethod
  			 and: [(s := self maybeSelectorOfMethod: cogMethod methodObject) notNil])
  				ifTrue: [self print: ' (nil: '; printStringOf: s; print: ')']
  				ifFalse: [self print: ' (nil)']]
  		ifFalse: [self space; printStringOf: cogMethod selector].
  	self cr!

Item was changed:
  ----- Method: CoInterpreter>>updateStackZoneReferencesToCompiledCodePreCompactionOnPage: (in category 'frame access') -----
  updateStackZoneReferencesToCompiledCodePreCompactionOnPage: thePage
  	<var: #thePage type: #'StackPage *'>
  	<inline: true>
  	| theFP callerFP theIPPtr theIP theMethodField theFlags theMethod |
  	theIPPtr := thePage headSP.
  	theFP := thePage  headFP.
  	[(self isMachineCodeFrame: theFP) ifTrue:
  		[theMethodField := self frameMethodField: theFP.
  		 theFlags := theMethodField bitAnd: MFMethodFlagsMask.
  		 theMethod := self cCoerceSimple: theMethodField - theFlags to: #'CogMethod *'.
+ 		 theMethod isCMBlock ifTrue:
- 		 theMethod cmType = CMBlock ifTrue:
  			[theMethod := (self cCoerceSimple: theMethodField - theFlags to: #'CogBlockMethod *') cmHomeMethod].
  		 theIP := (stackPages longAt: theIPPtr) asUnsignedInteger.
  		 (theIP ~= cogit ceCannotResumePC
  		  and: [self asserta: (theIP >= theMethod asUnsignedInteger
  					   and: [theIP < (theMethod asUnsignedInteger + theMethod blockSize)])]) ifTrue:
  			[stackPages
  				longAt: theIPPtr
  				put: theIP + theMethod objectHeader].
  		 stackPages
  			longAt: theFP + FoxMethod
  			put: theMethodField + theMethod objectHeader].
  	 (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  		[theIPPtr := theFP + FoxCallerSavedIP.
  		 theFP := callerFP]!

Item was changed:
  ----- Method: CogBlockMethod>>cpicHasMNUCase (in category 'accessing') -----
  cpicHasMNUCase
  	"Answer if the receiver has an MNU case."
  	<inline: true>
  
  	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self isCMClosedPIC]]
- 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self cmType = CMClosedPIC]]
  		ifFalse: [cpicHasMNUCaseOrCMIsFullBlock]!

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

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

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

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

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

Item was changed:
  ----- Method: CogMethodSurrogate>>cmIsFullBlock (in category 'accessing') -----
  cmIsFullBlock
  	"Answer the value of cpicHasMNUCaseOrCMIsFullBlock"
+ 	self assert: (self isCMMethodEtAl or: [self isCMBlock]).
- 	self assert: (self cmType = CMMethod or: [self cmType = CMBlock]).
  	^SistaV1BytecodeSet
  		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock]
  		ifFalse: [false]!

Item was changed:
  ----- Method: CogMethodSurrogate>>cpicHasMNUCase (in category 'accessing') -----
  cpicHasMNUCase
  	"Answer if the receiver has an MNU case."
  	<inline: true>
  
  	^SistaV1BytecodeSet
+ 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self isCMClosedPIC]]
- 		ifTrue: [self cpicHasMNUCaseOrCMIsFullBlock and: [self cmType = CMClosedPIC]]
  		ifFalse: [self cpicHasMNUCaseOrCMIsFullBlock]!

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

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

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

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

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

Item was changed:
  ----- Method: CogMethodSurrogate>>menuPrompt (in category 'breakpoints') -----
  menuPrompt
  	^String streamContents:
  		[:s|
  		 s
  			nextPut: $(;
  			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>>addToOpenPICList: (in category 'accessing') -----
  addToOpenPICList: anOpenPIC
  	<var: #anOpenPIC type: #'CogMethod *'>
+ 	self assert: anOpenPIC isCMOpenPIC.
+ 	self assert: (openPICList == nil or: [openPICList isCMOpenPIC]).
- 	self assert: anOpenPIC cmType = CMOpenPIC.
- 	self assert: (openPICList == nil
- 				or: [openPICList cmType = CMOpenPIC]).
  	cogit assertValidDualZoneWriteAddress: anOpenPIC.
  	anOpenPIC nextOpenPIC: openPICList asUnsignedInteger.
  	openPICList := cogit cCoerceSimple: anOpenPIC asUnsignedInteger - cogit getCodeToDataDelta to: #'CogMethod *'.
  	self cCode: '' inSmalltalk: [self deny: openPICList isInteger]!

Item was changed:
  ----- Method: CogMethodZone>>addToUnpairedMethodList: (in category 'accessing') -----
  addToUnpairedMethodList: aCogMethod
  	<option: #NewspeakVM>
  	<var: #aCogMethod type: #'CogMethod *'>
+ 	self assert: aCogMethod isCMMethodEtAl.
- 	self assert: aCogMethod cmType = CMMethod.
  	self assert: (cogit noAssertMethodClassAssociationOf: aCogMethod methodObject) = objectMemory nilObject.
  	self assert: (unpairedMethodList == nil
+ 				or: [(self cCoerceSimple: unpairedMethodList to: #'CogMethod *') isCMMethodEtAl]).
- 				or: [(self cCoerceSimple: unpairedMethodList to: #'CogMethod *') cmType = CMMethod]).
  	cogit assertValidDualZoneWriteAddress: aCogMethod.
  	aCogMethod nextMethodOrIRCs: unpairedMethodList.
  	unpairedMethodList := aCogMethod asUnsignedInteger - cogit getCodeToDataDelta!

Item was changed:
  ----- Method: CogMethodZone>>clearCogCompiledCode (in category 'jit - api') -----
  clearCogCompiledCode
  	"Free all methods. Do it the slow way to keep methodBytesFreedSinceLastCompaction accurate."
  	<inline: true>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	NewspeakVM ifTrue: [unpairedMethodList := nil].
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[self freeMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod].
  	self manageFrom: baseAddress to: limitAddress!

Item was changed:
  ----- Method: CogMethodZone>>clearSavedPICUsageCount: (in category 'compaction') -----
  clearSavedPICUsageCount: cogMethod
  	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
  	<inline: #always>
  	(SistaVM
+ 	 and: [cogMethod isCMClosedPIC]) ifTrue:
- 	 and: [cogMethod cmType = CMClosedPIC]) ifTrue:
  		[cogMethod blockEntryOffset: 0]!

Item was changed:
  ----- Method: CogMethodZone>>compactCompiledCode (in category 'compaction') -----
  compactCompiledCode
  	| objectHeaderValue source dest writableVersion bytes |
  	<var: #source type: #'CogMethod *'>
  	<var: #dest type: #'CogMethod *'>
  	compactionInProgress := true.
  	methodCount := 0.
  	objectHeaderValue := objectMemory nullHeaderForMachineCodeMethod.
  	source := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	self voidOpenPICList. "The(se) list(s) will be rebuilt with the current live set"
  	self voidUnpairedMethodList.
  	[source < self limitZony
+ 	 and: [source isCMFree not]] whileTrue:
- 	 and: [source cmType ~= CMFree]] whileTrue:
  		[self assert: (cogit cogMethodDoesntLookKosher: source) = 0.
  		 writableVersion := cogit writableMethodFor: source. 
  		 writableVersion objectHeader: objectHeaderValue.
  		 source cmUsageCount > 0 ifTrue:
  			[writableVersion cmUsageCount: source cmUsageCount // 2].
  		 self maybeLinkOnUnpairedMethodList: source.
  		 self clearSavedPICUsageCount: writableVersion.
+ 		 source isCMOpenPIC ifTrue:
- 		 source cmType = CMOpenPIC ifTrue:
  			[self addToOpenPICList: writableVersion].
  		 methodCount := methodCount + 1.
  		 source := self methodAfter: source].
  	source >= self limitZony ifTrue:
  		[^self halt: 'no free methods; cannot compact.'].
  	dest := source.
  	[source < self limitZony] whileTrue:
  		[self assert: (cogit maybeFreeCogMethodDoesntLookKosher: source) = 0.
  		 bytes := source blockSize.
+ 		 source isCMFree ifFalse:
- 		 source cmType ~= CMFree ifTrue:
  			[methodCount := methodCount + 1.
  			 cogit
  				codeMemmove: dest _: source _: bytes;
  				maybeFlushWritableZoneFrom: dest asUnsignedInteger to: dest asUnsignedInteger + bytes.
  			 (writableVersion := cogit writableMethodFor: dest) objectHeader: objectHeaderValue.
+ 			 dest isCMMethodEtAl
- 			 dest 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 update the original method's header if it is referring to this CogMethod."
  					 (coInterpreter rawHeaderOf: dest methodObject) asInteger = source asInteger
  						ifTrue:
  							[coInterpreter rawHeaderOf: dest methodObject put: dest asInteger]
  						ifFalse:
  							[self assert: (cogit noAssertMethodClassAssociationOf: dest methodObject) = objectMemory nilObject.
  							 self linkOnUnpairedMethodList: dest]]
  				ifFalse:
  					[self clearSavedPICUsageCount: writableVersion.
+ 					 dest isCMOpenPIC ifTrue:
- 					 dest cmType = CMOpenPIC ifTrue:
  						[self addToOpenPICList: writableVersion]].
  			 dest cmUsageCount > 0 ifTrue:
  				[writableVersion cmUsageCount: dest cmUsageCount // 2].
  			 cogit maybeFlushWritableZoneFrom: dest asUnsignedInteger to: (dest + 1) asUnsignedInteger.
  			 dest := coInterpreter cCoerceSimple: dest asUnsignedInteger + bytes to: #'CogMethod *'].
  		 source := coInterpreter cCoerceSimple: source asUnsignedInteger + bytes to: #'CogMethod *'].
  	mzFreeStart := dest asUnsignedInteger.
  	methodBytesFreedSinceLastCompaction := 0.
  	compactionInProgress := false!

Item was changed:
  ----- Method: CogMethodZone>>findPreviouslyCompiledVersionOf:with: (in category 'accessing') -----
  findPreviouslyCompiledVersionOf: aMethodObj with: aSelectorOop
  	"Newspeak uses a set of methods to implement accessors, a setter and a getter for
  	 each inst var offset (e.g. 0 to 255).  These accessors are installed under the relevant
  	 selectors in different method dictionaries as required.  These methods effectively
  	 have multiple selectors.  The current inline cache design stores the selector of a
  	 linked send in the header of the target method.  So this requires a one-to-many
  	 mapping of bytecoded method to cog method, with the bytecoded method referring
  	 directly to only one cog method, which will have a specific selector, not necessarily
  	 the right one.  It is therefore worth-while searching for a cog method on this bytecoded
  	 method that has the right selector.  To speed up the search we maintain all such unpaired
  	 methods on the unpairedMethodList, which is linked through nextMethodOrIRCs."
  	<returnTypeC: #'CogMethod *'>
  	<option: #NewspeakVM>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	((coInterpreter methodHasCogMethod: aMethodObj)
  	 and: [(coInterpreter methodClassAssociationOf: aMethodObj) = objectMemory nilObject]) ifTrue:
  		[cogMethod := self cCoerceSimple: unpairedMethodList to: #'CogMethod *'.
  		[cogMethod notNil] whileTrue:
+ 			[self assert: cogMethod isCMMethodEtAl.
- 			[self assert: cogMethod cmType = CMMethod.
  			 (cogMethod selector = aSelectorOop
  			  and: [cogMethod methodObject = aMethodObj]) ifTrue:
  				[^cogMethod].
  			 cogMethod := self cCoerceSimple: cogMethod nextMethodOrIRCs to: #'CogMethod *']].
  	^nil!

Item was changed:
  ----- Method: CogMethodZone>>firstBogusYoungReferrer (in category 'young referers') -----
  firstBogusYoungReferrer
  	"Answer that all entries in youngReferrers are in-use and have the cmRefersToYoung flag set.
  	 Used to check that the youngreferrers pruning routines work correctly."
  	| pointer cogMethod |
  	<doNotGenerate>
  	(youngReferrers > limitAddress
  	 or: [youngReferrers < mzFreeStart]) ifTrue:
  		[^#invalidListPointers].
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
+ 		 cogMethod isCMFree ifFalse:
- 		 cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifFalse:
  				[^cogMethod].
  			 (self occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
  				[^cogMethod]].
  		 pointer := pointer + objectMemory wordSize].
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < mzFreeStart] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[(self occurrencesInYoungReferrers: cogMethod) ~= (cogMethod cmRefersToYoung ifTrue: [1] ifFalse: [0]) ifTrue:
  				[^cogMethod]].
  		 cogMethod := self methodAfter: cogMethod]..
  	^nil!

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 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:
  				[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]].
  		 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>>kosherYoungReferrers (in category 'young referers') -----
  kosherYoungReferrers
  	"Answer that all entries in youngReferrers are in-use and have the cmRefersToYoung flag set.
  	 Used to check that the youngreferrers pruning routines work correctly."
  	<api>
  	| pointer cogMethod prevMethod |
  	<var: #pointer type: #usqInt>
  	(youngReferrers > limitAddress
  	 or: [youngReferrers < mzFreeStart]) ifTrue:
  		[^false].
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
+ 		 cogMethod isCMFree ifFalse:
- 		 cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifFalse:
  				[^false].
  			 (self occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
  				[^false]].
  		 pointer := pointer + objectMemory wordSize].
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
  		[prevMethod := cogMethod.
+ 		 cogMethod isCMFree ifFalse:
- 		 cogMethod cmType ~= CMFree ifTrue:
  			[(self occurrencesInYoungReferrers: cogMethod) ~= (cogMethod cmRefersToYoung ifTrue: [1] ifFalse: [0]) ifTrue:
  				[^false]].
  		 cogMethod := self methodAfter: cogMethod.
  		 cogMethod = prevMethod ifTrue:
  			[^false]].
  	^true!

Item was changed:
  ----- Method: CogMethodZone>>maybeLinkOnUnpairedMethodList: (in category 'compaction') -----
  maybeLinkOnUnpairedMethodList: cogMethod
  	<inline: #always>
  	NewspeakVM ifTrue:
+ 		[(cogMethod isCMMethodEtAl
- 		[(cogMethod cmType = CMMethod
  		  and: [(coInterpreter rawHeaderOf: cogMethod methodObject) asInteger ~= cogMethod asInteger]) ifTrue:
  			[(cogit writableMethodFor: cogMethod) nextMethodOrIRCs: unpairedMethodList.
  			 unpairedMethodList := cogMethod asUnsignedInteger]]!

Item was changed:
  ----- Method: CogMethodZone>>methodsCompiledToMachineCodeInto: (in category 'method zone introspection') -----
  methodsCompiledToMachineCodeInto: arrayObj 
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	| cogMethod methodIndex |
  	methodIndex := 0.
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[objectMemory 
  				storePointerUnchecked: methodIndex 
  				ofObject: arrayObj 
  				withValue: cogMethod methodObject.
  			 methodIndex := methodIndex + 1].
  		 cogMethod := self methodAfter: cogMethod].
  	^ methodIndex
  	!

Item was changed:
  ----- Method: CogMethodZone>>methodsDo: (in category 'simulation only') -----
  methodsDo: aBlock
  	<doNotGenerate>
  	| cogMethod |
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[cogMethod isCMFree not ifTrue:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[aBlock value: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]
  	"<api>
  	<returnTypeC: #void>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[aBlock value: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]"!

Item was changed:
  ----- Method: CogMethodZone>>planCompaction (in category 'compaction') -----
  planCompaction
  	"Some methods have been freed.  Compute how much each survivor needs to
  	 move during the ensuing compaction and record it in the objectHeader field.
  
  	 For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
  	| delta cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	delta := 0.
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
+ 		[cogMethod isCMFree
- 		[cogMethod cmType = CMFree
  			ifTrue: [delta := delta - cogMethod blockSize]
  			ifFalse:
  				[self assert: (cogit cogMethodDoesntLookKosher: cogMethod) = 0.
  				 (cogit writableMethodFor: cogMethod) objectHeader: delta.
  				 SistaVM ifTrue:
  					[self savePICUsageCount: cogMethod]].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethodsWithMethod: (in category 'printing') -----
  printCogMethodsWithMethod: methodOop
  	<api>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[(cogMethod isCMFree not
- 		[(cogMethod cmType ~= CMFree
  		  and: [cogMethod methodObject = methodOop]) ifTrue:
  			[coInterpreter printCogMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethodsWithPrimitive: (in category 'printing') -----
  printCogMethodsWithPrimitive: primIdx
  	<api>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[(cogMethod isCMMethodEtAl
- 		[(cogMethod cmType = CMMethod
  		  and: [primIdx = (coInterpreter primitiveIndexOfMethod: cogMethod methodObject
  							header: cogMethod methodHeader)]) ifTrue:
  			[coInterpreter printCogMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>printCogMethodsWithSelector: (in category 'printing') -----
  printCogMethodsWithSelector: selectorOop
  	<api>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony] whileTrue:
+ 		[(cogMethod isCMFree not
- 		[(cogMethod cmType ~= CMFree
  		  and: [cogMethod selector = selectorOop]) ifTrue:
  			[coInterpreter printCogMethod: cogMethod].
  		 cogMethod := self methodAfter: cogMethod]!

Item was changed:
  ----- Method: CogMethodZone>>printCogYoungReferrers (in category 'printing') -----
  printCogYoungReferrers
  	<api>
  	<returnTypeC: #void>
  	| pointer cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifFalse:
  			[coInterpreter print: '*'].
+ 		 cogMethod isCMFree ifTrue:
- 		 cogMethod cmType = CMFree ifTrue:
  			[coInterpreter print: '!!'].
+ 		 (cogMethod cmRefersToYoung and: [cogMethod isCMFree not]) ifFalse:
- 		 (cogMethod cmRefersToYoung and: [cogMethod cmType ~= CMFree]) ifFalse:
  			[coInterpreter print: ' '].
  		 coInterpreter printCogMethod: cogMethod.
  		 pointer := pointer + objectMemory wordSize]!

Item was changed:
  ----- Method: CogMethodZone>>relocateAndPruneYoungReferrers (in category 'young referers') -----
  relocateAndPruneYoungReferrers
  	| source dest next cogMethod |
  	<var: #source type: #usqInt>
  	<var: #dest type: #usqInt>
  	<var: #next type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: false>
  
  	self assert: youngReferrers <= limitAddress.
  	youngReferrers = limitAddress ifTrue:
  		[^nil].
  	dest := limitAddress.
  	[next := dest - objectMemory wordSize.
  	 next >= youngReferrers
+ 	 and: [(cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: next) to: #'CogMethod *') isCMFree not
- 	 and: [(cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: next) to: #'CogMethod *') cmType ~= CMFree
  	 and: [cogMethod cmRefersToYoung]]] whileTrue:
  		[cogMethod objectHeader ~= 0 ifTrue:
  			[cogit codeLongAt: next put: cogMethod asInteger + cogMethod objectHeader].
  		 dest := next].
  	self assert: dest >= youngReferrers.
  	source := dest - objectMemory wordSize.
  	[source >= youngReferrers] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: source) to: #'CogMethod *'.
+ 		 (cogMethod isCMFree not
- 		 (cogMethod cmType ~= CMFree
  		  and: [cogMethod cmRefersToYoung]) ifTrue:
  			[self assert: source < (dest - objectMemory wordSize).
  			 cogMethod objectHeader ~= 0 ifTrue:
  				[cogMethod := coInterpreter
  									cCoerceSimple: cogMethod asInteger + cogMethod objectHeader asInteger
  									to: #'CogMethod *'].
  			 cogit codeLongAt: (dest := dest - objectMemory wordSize) put: cogMethod asInteger].
  		 source := source - objectMemory wordSize].
  	youngReferrers := dest.
  	"this assert must be deferred until after compaction.  See the end of compactCogCompiledCode"
  	"self assert: self kosherYoungReferrers"!

Item was changed:
  ----- Method: CogMethodZone>>relocateMethodsPreCompaction (in category 'compaction') -----
  relocateMethodsPreCompaction
  	"All surviving methods have had the amount they are going to relocate by
  	 stored in their objectHeader fields.  Relocate all relative calls so that after
  	 the compaction of both the method containing each call and the call target
  	 the calls invoke the same target."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := cogit cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod asUnsignedInteger < mzFreeStart] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
+ 			[cogMethod isCMClosedPIC
- 		[cogMethod cmType ~= CMFree ifTrue:
- 			[cogMethod cmType = CMClosedPIC
  				ifTrue: [cogit relocateCallsInClosedPIC: cogMethod]
  				ifFalse: [cogit relocateCallsAndSelfReferencesInMethod: cogMethod]].
  		 cogMethod := self methodAfter: cogMethod].
  	self relocateAndPruneYoungReferrers.
  	^true!

Item was changed:
  ----- Method: CogMethodZone>>removeFromOpenPICList: (in category 'accessing') -----
  removeFromOpenPICList: anOpenPIC
  	<var: #anOpenPIC type: #'CogMethod *'>
  	| prevPIC |
  	<var: #prevPIC type: #'CogMethod *'>
+ 	self assert: anOpenPIC isCMOpenPIC.
- 	self assert: anOpenPIC cmType = CMOpenPIC.
  	openPICList ifNil: [^nil]. "As it is when compacting or unlinking all sends"
+ 	self assert: (openPICList isCMOpenPIC
- 	self assert: (openPICList cmType = CMOpenPIC
  				and: [openPICList nextOpenPIC isNil
+ 					or: [(self cCoerceSimple: openPICList nextOpenPIC to: #'CogMethod *') isCMOpenPIC]]).
- 					or: [(self cCoerceSimple: openPICList nextOpenPIC to: #'CogMethod *') cmType = CMOpenPIC]]).
  	anOpenPIC = openPICList ifTrue:
  		["N.B. Use self rather than coInterpreter to avoid attempting to cast nil.
  		  Conversion to CogMethod done in the nextOpenPIC accessor."
  		 openPICList := self cCoerceSimple: anOpenPIC nextOpenPIC to: #'CogMethod *'.
  		 ^nil].
  	prevPIC := openPICList.
  	[self assert: (prevPIC ~~ nil
+ 				and: [prevPIC isCMOpenPIC]).
- 				and: [prevPIC cmType = CMOpenPIC]).
  	 prevPIC nextOpenPIC = anOpenPIC asUnsignedInteger ifTrue:
  		[(cogit writableMethodFor: prevPIC) nextOpenPIC: anOpenPIC nextOpenPIC.
  		 ^nil].
  	  prevPIC := self cCoerceSimple: prevPIC nextOpenPIC to: #'CogMethod *'.
  	  true] whileTrue!

Item was changed:
  ----- Method: CogMethodZone>>removeFromUnpairedMethodList: (in category 'accessing') -----
  removeFromUnpairedMethodList: aCogMethod
  	<option: #NewspeakVM>
  	<var: #aCogMethod type: #'CogMethod *'>
  	| prevMethod |
  	<var: #prevMethod type: #'CogMethod *'>
+ 	self assert: aCogMethod isCMMethodEtAl.
- 	self assert: aCogMethod cmType = CMMethod.
  	aCogMethod asUnsignedInteger = unpairedMethodList ifTrue:
  		[unpairedMethodList := aCogMethod nextMethodOrIRCs.
  		 ^nil].
  	prevMethod := self cCoerceSimple: unpairedMethodList to: #'CogMethod *'.
  	[prevMethod notNil] whileTrue:
+ 		[self assert: (prevMethod ~~ nil and: [prevMethod isCMMethodEtAl]).
- 		[self assert: (prevMethod ~~ nil and: [prevMethod cmType = CMMethod]).
  		 prevMethod nextMethodOrIRCs = aCogMethod asUnsignedInteger ifTrue:
  			[prevMethod nextMethodOrIRCs: aCogMethod nextMethodOrIRCs.
  			 ^nil].
  		  prevMethod := self cCoerceSimple: prevMethod nextMethodOrIRCs to: #'CogMethod *']!

Item was changed:
  ----- Method: CogMethodZone>>restorePICUsageCount: (in category 'compaction') -----
  restorePICUsageCount: cogMethod
  	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
  	<var: #cogMethod type: #'CogMethod *'>
  	<option: #SistaVM>
+ 	(cogMethod isCMClosedPIC
- 	(cogMethod cmType = CMClosedPIC
  	 and: [cogMethod blockEntryOffset ~= 0]) ifTrue:
  		[cogMethod
  			cmUsageCount: cogMethod blockEntryOffset;
  			blockEntryOffset: 0]!

Item was changed:
  ----- Method: CogMethodZone>>savePICUsageCount: (in category 'compaction') -----
  savePICUsageCount: cogMethod
  	"For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
  	<var: #cogMethod type: #'CogMethod *'>
  	<option: #SistaVM>
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod
  			blockEntryOffset: cogMethod cmUsageCount;
  			cmUsageCount: 0]!

Item was changed:
  ----- Method: CogMethodZone>>shouldFreeMethod:given: (in category 'compaction') -----
  shouldFreeMethod: cogMethod given: freeableUsage
  	"Answer if cogMethod should be freed in the current pass of freeOlderMethodsForCompaction.
  
  	 For Sista, where we want PICs to last so they can be observed, we need to keep PICs unless
  	 they are definitely unused.  So we need to identify unused PICs.  So in planCompact, zero the
  	 usage counts of all PICs, saving the actual usage count in blockEntryOffset.  Then in
  	 relocateMethodsPreCompaction (actually in relocateIfCallOrMethodReference:mcpc:delta:)
  	 restore the usage counts of used PICs.  Finally in compactCompiledCode, clear the blockEntryOffset
  	 of the unused PICs; they will then have a zero count and be reclaimed in the next code compaction."
+ 
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	^SistaVM
  		ifTrue:
+ 			[cogMethod isCMMethodEtAl
+ 				ifTrue: [cogMethod cmUsageCount <= freeableUsage]
+ 				ifFalse: [cogMethod isCMFree not and: [cogMethod cmUsageCount = 0]]]
- 			[cogMethod cmType = CMMethod
- 			 	ifTrue: [cogMethod cmUsageCount <= freeableUsage]
- 				ifFalse: [cogMethod cmType ~= CMFree
- 						  and: [cogMethod cmUsageCount = 0]]]
  		ifFalse:
+ 			[cogMethod isCMFree not
+ 			 and: [cogMethod cmUsageCount <= freeableUsage]]!
- 			[cogMethod cmType ~= CMFree
- 			  and: [cogMethod cmUsageCount <= freeableUsage]]!

Item was changed:
  ----- Method: CogMethodZone>>summarizeZone (in category 'printing') -----
  summarizeZone
  	<doNotGenerate>
  	| pointer cogMethod ny nf nn |
  	<var: #cogMethod type: #'CogMethod *'>
  	self printCogMethodsSummarizing: true.
  	self printOpenPICListSummarizing: true.
  	ny := nf := nn := 0.
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifTrue:
  			[ny := ny + 1].
+ 		 cogMethod isCMFree ifTrue:
- 		 cogMethod cmType = CMFree ifTrue:
  			[nf := nf + 1].
+ 		 (cogMethod cmRefersToYoung or: [cogMethod isCMFree]) ifFalse:
- 		 (cogMethod cmRefersToYoung or: [cogMethod cmType = CMFree]) ifFalse:
  			[nn := nn + 1].
  		 pointer := pointer + objectMemory wordSize].
  	coInterpreter print: 'num free '; printNum: nf; print: ' num young '; printNum: ny; print: ' num neither '; printNum: nn; cr!

Item was changed:
  ----- Method: CogMethodZone>>voidYoungReferrersPostTenureAll (in category 'jit - api') -----
  voidYoungReferrersPostTenureAll
  	<var: #cogMethod type: #'CogMethod *'>
  	| pointer cogMethod |
  	<var: #pointer type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: youngReferrers <= limitAddress.
  	pointer := youngReferrers.
  	[pointer < limitAddress] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
+ 		 cogMethod isCMFree ifFalse:
- 		 cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung: false].
  		 pointer := pointer + objectMemory wordSize].
  	youngReferrers := limitAddress!

Item was changed:
  ----- Method: CogVMSimulator>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  	| cPIC |
  	cPIC := self cCoerceSimple: self stackTop - cogit mnuOffset to: #'CogMethod *'.
+ 	self assert: (cPIC isCMClosedPIC or: [cPIC isCMOpenPIC]).
- 	self assert: (cPIC cmType = CMClosedPIC or: [cPIC cmType = CMOpenPIC]).
  	self mnuBreakpoint: cPIC selector receiver: nil.
  	^super ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr!

Item was changed:
  ----- Method: Cogit>>addCogMethodsToHeapMap (in category 'debugging') -----
  addCogMethodsToHeapMap
  	<api>
  	"Perform an integrity/leak check using the heapMap.
  	 Set a bit at each cog method's header."	
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[coInterpreter heapMapAtWord: cogMethod Put: 1].
  		cogMethod := methodZone methodAfter: cogMethod]!

Item was changed:
  ----- Method: Cogit>>allCogMethodsFor: (in category 'disassembly') -----
  allCogMethodsFor: cogMethod
  	<doNotGenerate>
  	| blockEntry end methods pc |
  	cogMethod isInteger ifTrue: [^self allCogMethodsFor: (self cogMethodSurrogateAt: cogMethod)].
+ 	cogMethod isCMBlock ifTrue:
- 	cogMethod cmType = CMBlock ifTrue:
  		[^self allCogMethodsFor: cogMethod cmHomeMethod].
+ 	(cogMethod isCMMethodEtAl not
- 	(cogMethod cmType ~= CMMethod
  	 or: [cogMethod blockEntryOffset = 0]) ifTrue:
  		[^{cogMethod}].
  
  	methods := OrderedCollection with: cogMethod.
  	pc := blockEntry := cogMethod blockEntryOffset + cogMethod asInteger.
  	end := (self mapEndFor: cogMethod) - 1.
  	[pc < end] whileTrue:
  		[| targetpc |
  		 targetpc := blockEntry.
  		 (backEnd isJumpAt: pc) ifTrue:
  			[targetpc := backEnd jumpTargetPCAt: pc.
  			 targetpc < blockEntry ifTrue:
  				[methods add: (self cCoerceSimple: targetpc - (self sizeof: CogBlockMethod) to: #'CogBlockMethod *')]].
  		 pc := pc + (backEnd instructionSizeAt: pc)].
  	^methods sort!

Item was changed:
  ----- 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') -----
  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>>cPICCompactAndIsNowEmpty: (in category 'in-line cacheing') -----
  cPICCompactAndIsNowEmpty: cPIC
  	"Scan the CPIC for target methods that have been freed and eliminate them.
  	 Since the first entry cannot be eliminated, answer that the PIC should be
  	 freed if the first entry is to a free target.  Answer if the PIC is now empty or should be freed."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc entryPoint targetMethod targets tags methods used |
  	<var: #targetMethod	type: #'CogMethod *'>
  	<var: #tags			declareC: 'int tags[MaxCPICCases]'>
  	<var: #targets			declareC: 'sqInt targets[MaxCPICCases]'>
  	<var: #methods		declareC: 'sqInt methods[MaxCPICCases]'>
+ 	self cCode: '' inSmalltalk:
- 	self cCode: [] inSmalltalk:
  		[tags := CArrayAccessor on: (Array new: MaxCPICCases).
  		 targets := CArrayAccessor on: (Array new: MaxCPICCases).
  		 methods := CArrayAccessor on: (Array new: MaxCPICCases)].
  	used := 0.
  	1 to: cPIC cPICNumCases do:
  		[:i| | valid |
  		 pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		 entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		 valid := true.
  		 "Collect all target triples except for triples whose entry-point is a freed method"
  		 (cPIC containsAddress: entryPoint) ifFalse:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 			 self assert: (targetMethod isCMMethodEtAl or: [targetMethod isCMFree]).
+ 			 targetMethod isCMFree ifTrue:
- 			 self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
- 			 targetMethod cmType = CMFree ifTrue:
  				[i = 1 ifTrue: [^true]. "cannot filter out the first entry cuz classTag is at point of send."
  				 valid := false]].
  		 valid ifTrue:
  			[tags at: used put: (i > 1 ifTrue: [backEnd literal32BeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize]).
  			 targets at: used put: entryPoint.
  			 methods at: used put: (backEnd literalBeforeFollowingAddress: pc - (i = 1
  																				ifTrue: [backEnd jumpLongByteSize]
  																				ifFalse: [backEnd jumpLongConditionalByteSize + backEnd cmpC32RTempByteSize])).
  			 used := used + 1]].
  	used = cPIC cPICNumCases ifTrue:
  		[^false].
  	used = 0 ifTrue:
  		[^true].
  
  	(self writableMethodFor: cPIC) cPICNumCases: used.
  	used = 1 ifTrue:
  		[pc := self addressOfEndOfCase: 2 inCPIC: cPIC.
  		 self rewriteCPIC: cPIC caseJumpTo: pc.
  		 ^false].
  	"the first entry cannot change..."
  	1 to: used - 1 do:
  		[:i|
  		 pc := self addressOfEndOfCase: i + 1 inCPIC: cPIC.
  		 self rewriteCPICCaseAt: pc tag: (tags at: i) objRef: (methods at: i) target: (targets at: i)].
  
  	"finally, rewrite the jump 3 instr before firstCPICCaseOffset to jump to the beginning of this new case"
  	self rewriteCPIC: cPIC caseJumpTo: pc - cPICCaseSize.
  	^false!

Item was changed:
  ----- Method: Cogit>>cPICHasFreedTargets: (in category 'in-line cacheing') -----
  cPICHasFreedTargets: cPIC
  	"scan the CPIC for target methods that have been freed. "
  	<var: #cPIC type: #'CogMethod *'>
  	| pc entryPoint targetMethod |
- 	<var: #targetMethod type: #'CogMethod *'>
  
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		"Find target from jump.  Ignore jumps to the interpret and MNU calls within this PIC"
  		(cPIC containsAddress: entryPoint) ifFalse:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 			 self assert: (targetMethod isCMMethodEtAl or: [targetMethod isCMFree]).
+ 			 targetMethod isCMFree ifTrue:
- 			 self assert: (targetMethod cmType = CMMethod or: [targetMethod cmType = CMFree]).
- 			 targetMethod cmType = CMFree ifTrue:
  				[^true]]].
  	^false!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	<static: true>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack asUnsignedInteger.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	(objectMemory isOopForwarded: receiver) ifTrue:
  		[^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	outerReturn := coInterpreter stackTop asUnsignedInteger.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [(backEnd inlineCacheTagAt: outerReturn) = self picAbortDiscriminatorValue
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	self ensureWritableCodeZone.
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	(pic isNil or: [self allowEarlyOpenPICPromotion not]) ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			 self ensureExecutableCodeZone.
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod]].
  	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
  	 for the benefit of the cacheTag assert check in checkIfValidOopRef:pc:cogMethod: et al."
+ 	extent := pic isCMOpenPIC
- 	extent := pic cmType = CMOpenPIC
  				ifTrue:
  					[backEnd
  						rewriteInlineCacheAt: outerReturn
  						tag: (backEnd
  								inlineCacheValueForSelector: targetMethod selector
  								in: coInterpreter mframeHomeMethodExport)
  						target: pic asInteger + cmEntryOffset]
  				ifFalse:
  					[backEnd
  						rewriteCallAt: outerReturn
  						target: pic asInteger + cmEntryOffset].
  
  	self assertValidDualZoneFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
  	"These also implicitly flush the read/write mapped dual zone to the read/execute zone."
  	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
  	backEnd flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogPIC: pic
  		fromLinkedSendWithReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- 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') -----
  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>>checkIntegrityOfObjectReferencesInCode: (in category 'debugging') -----
  checkIntegrityOfObjectReferencesInCode: gcModes
  	<api>
  	"Answer if all references to objects in machine-code are valid."	
  	| cogMethod ok count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	ok := true.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMFree not ifTrue:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifTrue:
  				[(count := methodZone occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
  					[coInterpreter print: 'young referrer CM '; printHex: cogMethod asInteger.
  					 count = 0
  						ifTrue: [coInterpreter print: ' is not in youngReferrers'; eekcr]
  						ifFalse: [coInterpreter print: ' is in youngReferrers '; printNum: count; print: ' times!!'; eekcr].
  					 ok := false]].
  			 (objectRepresentation checkValidOopReference: cogMethod selector) ifFalse:
  				[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' selector'; eekcr.
  				 ok := false].
+ 			 cogMethod isCMMethodEtAl
- 			 cogMethod cmType = CMMethod
  				ifTrue:
  					[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  					 (objectRepresentation checkValidObjectReference: cogMethod methodObject) ifFalse:
  						[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' methodObject'; eekcr.
  						 ok := false].
  					 (objectMemory isOopCompiledMethod: cogMethod methodObject) ifFalse:
  						[coInterpreter print: 'non-method in CM '; printHex: cogMethod asInteger; print: ' methodObject'; eekcr.
  						 ok := false].
  					 (self mapFor: cogMethod
  						 performUntil: #checkIfValidOopRef:pc:cogMethod:
  						 arg: cogMethod) ~= 0
  							ifTrue: [ok := false].
  					 (objectRepresentation hasSpurMemoryManagerAPI
  					  or: [gcModes anyMask: GCModeNewSpace]) ifTrue:
  						[(((objectMemory isYoungObject: cogMethod methodObject)
  						    or: [objectMemory isYoung: cogMethod selector])
  						   and: [cogMethod cmRefersToYoung not]) ifTrue:
  							[coInterpreter print: 'CM '; printHex: cogMethod asInteger; print: ' refers to young but not marked as such'; eekcr.
  							 ok := false]]]
  				ifFalse:
+ 					[cogMethod isCMClosedPIC
- 					[cogMethod cmType = CMClosedPIC
  						ifTrue:
  							[(self checkValidObjectReferencesInClosedPIC: cogMethod) ifFalse:
  								[ok := false]]
  						ifFalse:
+ 							[cogMethod isCMOpenPIC
- 							[cogMethod cmType = CMOpenPIC
  								ifTrue:
  									[(self mapFor: cogMethod
  										performUntil: #checkIfValidOopRef:pc:cogMethod:
  										arg: cogMethod) ~= 0
  											ifTrue: [ok := false]]]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	^ok!

Item was changed:
  ----- Method: Cogit>>cleanUpFailingCogCodeConstituents: (in category 'profiling primitives') -----
  cleanUpFailingCogCodeConstituents: cogMethodArg
  	<var: #cogMethodArg type: #'CogMethod *'>
  	<inline: #never> "i.e. this should never be called, so keep it out of the main path."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := cogMethodArg.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMClosedPIC ifTrue:
- 		[cogMethod cmType = CMClosedPIC ifTrue:
  			[cogMethod methodObject: 0].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"would like to assert this, but it requires the leak checked be run :-(
  		self assert: self allMachineCodeObjectReferencesValid."
  	coInterpreter popRemappableOop.
  	^nil!

Item was changed:
  ----- Method: Cogit>>codeRangesFor: (in category 'disassembly') -----
  codeRangesFor: cogMethod
  	"Answer a sequence of ranges of code for the main method and all of the blocks in a CogMethod.
  	 N.B.  These are in order of block dispatch, _not_ necessarily address order in the method."
  	<doNotGenerate>
  	| pc end blockEntry starts |
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[end := false
  					ifTrue: [cogMethod asInteger + cPICEndOfCodeOffset - backEnd jumpLongByteSize]
  					ifFalse: [cogMethod asInteger + closedPICSize - 1].
  		 ^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
  				startpc: nil }].
  	end := (self mapEndFor: cogMethod) - 1.
  	cogMethod blockEntryOffset = 0 ifTrue:
  		[^{ CogCodeRange
  				from: cogMethod asInteger + (self sizeof: CogMethod)
  				to: end
  				cogMethod: cogMethod
+ 				startpc: (cogMethod isCMOpenPIC ifFalse:
- 				startpc: (cogMethod cmType ~= CMOpenPIC ifTrue:
  							[coInterpreter startPCOfMethodHeader: cogMethod methodHeader]) }].
  	pc := blockEntry := cogMethod blockEntryOffset + cogMethod asInteger.
  	starts := OrderedCollection with: cogMethod.
  	[pc < end] whileTrue:
  		[| targetpc |
  		 targetpc := blockEntry.
  		 (backEnd isJumpAt: pc) ifTrue:
  			[targetpc := backEnd jumpTargetPCAt: pc.
  			 targetpc < blockEntry ifTrue:
  				[starts add: (self cCoerceSimple: targetpc - (self sizeof: CogBlockMethod) to: #'CogBlockMethod *')]].
  		 pc := pc + (backEnd instructionSizeAt: pc)].
  	starts := starts asSortedCollection.
  	^(1 to: starts size + 1) collect:
  		[:i| | cogSubMethod nextpc |
  		i <= starts size
  			ifTrue:
  				[cogSubMethod := starts at: i.
  				 nextpc := i < starts size ifTrue: [(starts at: i + 1) address] ifFalse: [blockEntry].
  				 CogCodeRange
  					from: cogSubMethod address + (self sizeof: cogSubMethod)
  					to: nextpc - 1
  					cogMethod: cogSubMethod
  					startpc: (i = 1
  								ifTrue: [coInterpreter startPCOfMethodHeader: cogMethod methodHeader]
  								ifFalse: [cogSubMethod startpc])]
  			ifFalse:
  				[CogCodeRange
  					from: blockEntry
  					to: end]]!

Item was changed:
  ----- Method: Cogit>>cogCodeConstituents: (in category 'profiling primitives') -----
  cogCodeConstituents: withDetails
  	"Answer the contents of the code zone as an array of pair-wise element, address in ascending address order.
  	 Answer a string for a runtime routine or abstract label (beginning, end, etc), a CompiledMethod for a CMMethod,
  	 or a selector (presumably a Symbol) for a PIC.
  	 If withDetails is true
  		- answer machine-code to bytecode pc mapping information for methods
  		- answer class, target pair information for closed PIC
  	 N.B. Since the class tag for the first case of a closed PIC is stored at the send site, it must be collected
  		  by scanning methods (see collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:).  Since closed PICs
  		  are never shared they always come after the method that references them, so we don't need an extra pass
  		  to collect the first case class tags, which are (temporarily) assigned to each closed PIC's methodObject field.
  		  But we do need to reset the methodObject fields to zero.  This is done in createPICData:, unless memory
  		  runs out, in which case it is done by cleanUpFailingCogCodeConstituents:."
  	<api>
  	| count cogMethod constituents label value |
  	<var: #cogMethod type: #'CogMethod *'>
  	count := trampolineTableIndex / 2 + 3. "+ 3 for start, freeStart and end"
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[count := count + 1].
  		cogMethod := methodZone methodAfter: cogMethod].
  	constituents := coInterpreter instantiateClass: coInterpreter classArray indexableSize: count * 2.
  	constituents ifNil:
  		[^constituents].
  	coInterpreter pushRemappableOop: constituents.
  	((label := objectMemory stringForCString: 'CogCode') isNil
  	 or: [(value := self positiveMachineIntegerFor: codeBase) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: 0 ofObject: (self maybeTopRemapped: constituents) withValue: label;
  		storePointerUnchecked: 1 ofObject: (self maybeTopRemapped: constituents) withValue: value.
  	0 to: trampolineTableIndex - 1 by: 2 do:
  		[:i|
  		((label := objectMemory stringForCString: (trampolineAddresses at: i)) isNil
  		 or: [(value := self positiveMachineIntegerFor: (trampolineAddresses at: i + 1) asUnsignedInteger) isNil]) ifTrue:
  			[coInterpreter popRemappableOop.
  			 ^nil].
  		coInterpreter
  			storePointerUnchecked: 2 + i ofObject: (self maybeTopRemapped: constituents) withValue: label;
  			storePointerUnchecked: 3 + i ofObject: (self maybeTopRemapped: constituents) withValue: value].
  	count := trampolineTableIndex + 2.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMFree ifFalse:
- 		[cogMethod cmType ~= CMFree ifTrue:
  			[| profileData |
  			 profileData := self profileDataFor: cogMethod withDetails: withDetails.
  			 profileData ifNil: [^self cleanUpFailingCogCodeConstituents: cogMethod].
  			 coInterpreter
  				storePointerUnchecked: count
  				ofObject: (self maybeTopRemapped: constituents)
  				withValue: profileData.
  			value := withDetails
  						ifTrue: [self collectCogMethodConstituent: cogMethod]
  						ifFalse: [self positiveMachineIntegerFor: cogMethod asUnsignedInteger].
  			value ifNil: [^self cleanUpFailingCogCodeConstituents: cogMethod].
  			coInterpreter
  						storePointerUnchecked: count + 1
  						ofObject: (self maybeTopRemapped: constituents)
  						withValue: value.
  			 count := count + 2].
  		cogMethod := methodZone methodAfter: cogMethod].
  	((label := objectMemory stringForCString: 'CCFree') isNil
  	 or: [(value := self positiveMachineIntegerFor: methodZone zoneFree) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: count ofObject: (self maybeTopRemapped: constituents) withValue: label;
  		storePointerUnchecked: count + 1 ofObject: (self maybeTopRemapped: constituents) withValue: value.
  	((label := objectMemory stringForCString: 'CCEnd') isNil
  	 or: [(value := self positiveMachineIntegerFor: methodZone zoneEnd) isNil]) ifTrue:
  		[coInterpreter popRemappableOop.
  		 ^nil].
  	coInterpreter
  		storePointerUnchecked: count + 2 ofObject: (self maybeTopRemapped: constituents) withValue: label;
  		storePointerUnchecked: count + 3 ofObject: (self maybeTopRemapped: constituents) withValue: value.
  	constituents := coInterpreter popRemappableOop.
  	coInterpreter beRootIfOld: constituents.
  	"would like to assert this, but it requires the leak checked be run :-(
  		self assert: self allMachineCodeObjectReferencesValid."
  	^constituents!

Item was changed:
  ----- Method: Cogit>>cogMethodDoesntLookKosher: (in category 'debugging') -----
  cogMethodDoesntLookKosher: cogMethod
  	"Check that the header fields onf a non-free method are consistent with
  	 the type. Answer 0 if it is ok, otherwise answer a code for the error."
  	<api>
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	((cogMethod blockSize bitAnd: objectMemory wordSize - 1) ~= 0
  	 or: [cogMethod blockSize < (self sizeof: CogMethod)
  	 or: [cogMethod blockSize >= 32768]]) ifTrue:
  		[^1].
  
+ 	cogMethod isCMFree ifTrue: [^2].
- 	cogMethod cmType = CMFree ifTrue: [^2].
  
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[(objectMemory isIntegerObject: cogMethod methodHeader) ifFalse:
  			[^11].
  		 (objectRepresentation couldBeObject: cogMethod methodObject) ifFalse:
  			[^12].
  		 (cogMethod stackCheckOffset > 0
  		  and: [cogMethod stackCheckOffset < cmNoCheckEntryOffset]) ifTrue:
  			[^13].
  		 (SistaVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod counters ~= 0]]) ifTrue:
  			[(objectRepresentation couldBeDerivedObject: cogMethod counters) ifFalse:
  				[^14]].
  		 (NewspeakVM
  		  and: [objectRepresentation canPinObjects
  		  and: [cogMethod nextMethodOrIRCs ~= 0]]) ifTrue:
  			[(cogMethod nextMethodOrIRCs < methodZone zoneEnd)
  				ifTrue: "check the nextMethod (unpairedMethodList) unless we're compacting."
  					[(methodZone compactionInProgress
  					  or: [cogMethod nextMethodOrIRCs = (methodZone methodFor: cogMethod nextMethodOrIRCs asVoidPointer) asUnsignedInteger]) ifFalse:
  						[^15]]
  				ifFalse:
  					[(objectRepresentation couldBeDerivedObject: cogMethod nextMethodOrIRCs) ifFalse:
  						[^16]]].
  		 ^0].
  
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[cogMethod blockSize ~= openPICSize ifTrue:
  			[^21].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^22].
  		 "Check the nextOpenPIC link unless we're compacting"
  		 cogMethod objectHeader >= 0 ifTrue:
  			[(cogMethod methodObject = 0
  			  or: [methodZone compactionInProgress
  			  or: [cogMethod methodObject = (methodZone methodFor: cogMethod methodObject asVoidPointer) asUnsignedInteger]]) ifFalse:
  				[^23]].
  		 cogMethod stackCheckOffset ~= 0 ifTrue:
  			[^24].
  		 ^0].
  
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[cogMethod blockSize ~= closedPICSize ifTrue:
  			[^31].
  		 (cogMethod cPICNumCases between: 1 and: MaxCPICCases) ifFalse:
  			[^32].
  		 cogMethod methodHeader ~= 0 ifTrue:
  			[^33].
  		 cogMethod methodObject ~= 0 ifTrue:
  			[^34].
  		 ^0].
  
  	^9!

Item was changed:
  ----- Method: Cogit>>cogMethodOrBlockSurrogateAt: (in category 'simulation only') -----
  cogMethodOrBlockSurrogateAt: address
  	<doNotGenerate>
  	| surrogate |
  	surrogate := self cogMethodSurrogateAt: address.
+ 	^surrogate isCMBlock
- 	^surrogate cmType = CMBlock
  		ifTrue: [self cogBlockMethodSurrogateAt: address]
  		ifFalse: [surrogate]!

Item was changed:
  ----- Method: Cogit>>collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method: (in category 'profiling primitives') -----
  collectCogConstituentFor: descriptor Annotation: isBackwardBranchAndAnnotation Mcpc: mcpc Bcpc: bcpc Method: cogMethodArg
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #mcpc type: #'char *'>
  	<var: #cogMethodArg type: #'void *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| address entryPoint |
  	descriptor ifNil: [^0].
  	descriptor isMapped ifFalse: [^0].
  	address := self positiveMachineIntegerFor: mcpc asUnsignedInteger.
  	address ifNil: [^PrimErrNoMemory]. "This cannot trigger a GC but fails if not enough space in Eden,"
  	"Assumes we write the values into topRemappableOop"
  	coInterpreter
  		storePointerUnchecked: cogConstituentIndex
  		ofObject: coInterpreter topRemappableOop
  		withValue: address.
  	coInterpreter
  		storePointerUnchecked: cogConstituentIndex + 1
  		ofObject: coInterpreter topRemappableOop
  		withValue: (objectMemory integerObjectOf: bcpc).
  	cogConstituentIndex := cogConstituentIndex + 2.
  
  	"Collect any first case classTags for closed PICs."
  	((isBackwardBranchAndAnnotation noMask: 1)
  	 and: [self isSendAnnotation: isBackwardBranchAndAnnotation >> 1]) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "send is linked"
  			[self targetMethodAndSendTableFor: entryPoint annotation: isBackwardBranchAndAnnotation >> 1 into:
  				[:targetMethod :sendTable|
+ 				  targetMethod isCMClosedPIC ifTrue:
- 				  targetMethod cmType = CMClosedPIC ifTrue:
  					[targetMethod methodObject: (objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: mcpc asInteger))]]]].
  	^0!

Item was changed:
  ----- Method: Cogit>>collectCogMethodConstituent: (in category 'profiling primitives') -----
  collectCogMethodConstituent: cogMethod
  	"Answer a description of the mapping between machine code pointers and bytecode pointers for the Cog Method.
  	 First value is the address of the cog method.
  	 Following values are pairs of machine code pc and bytecode pc"
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #cogBlockMethod type: #'CogBlockMethod *'>
  	| nSlots errCode cogBlockMethod address data |
+ 	cogMethod isCMMethodEtAl 
- 	(cogMethod cmType = CMMethod) 
  		ifFalse: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger ].
  	cogBlockMethod := self cCoerceSimple: cogMethod to: #'CogBlockMethod *'.
  	cogBlockMethod stackCheckOffset = 0 "isFrameless ?"
  		ifTrue: [^self positiveMachineIntegerFor: cogMethod asUnsignedInteger].
  	nSlots := ((objectMemory byteSizeOf: cogMethod methodObject) - (coInterpreter startPCOfMethodHeader: cogMethod methodHeader)) * 2 + objectMemory minSlotsForShortening + 1."+1 for first address"
  	data := objectMemory instantiateClass: (objectMemory splObj: ClassArray) indexableSize: nSlots.
  	data ifNil: [^nil].
  	coInterpreter pushRemappableOop: data.
  	"The iteration assumes the object is the top remappable oop"
  	address := (self positiveMachineIntegerFor: cogMethod asUnsignedInteger).
  	address ifNil: [coInterpreter popRemappableOop. ^nil].
  	coInterpreter
  		storePointerUnchecked: 0
  		ofObject: coInterpreter topRemappableOop
  		withValue: address.
  	cogConstituentIndex := 1.
  	errCode := self
  		mapFor: cogBlockMethod
  		bcpc: (coInterpreter startPCOfMethod: cogMethod methodObject)
  		performUntil: #collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:
  		arg: cogMethod asVoidPointer.
  	errCode ~= 0 ifTrue: [coInterpreter popRemappableOop. ^nil].
  	cogConstituentIndex < nSlots ifTrue:
  		[objectMemory shorten: coInterpreter topRemappableOop toIndexableSize: cogConstituentIndex].
  	^coInterpreter popRemappableOop.!

Item was changed:
  ----- Method: Cogit>>compactPICsWithFreedTargets (in category 'compaction') -----
  compactPICsWithFreedTargets
  	| cogMethod count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	count := 0.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMClosedPIC
- 		[(cogMethod cmType = CMClosedPIC
  		  and: [self cPICCompactAndIsNowEmpty: cogMethod]) ifTrue:
  			[(self writableMethodFor: cogMethod) cmType: CMFree].
  		 cogMethod := methodZone methodAfter: cogMethod.
  		 count := count + 1].
  	self assert: count = methodZone numMethods!

Item was changed:
  ----- Method: Cogit>>createCPICData: (in category 'profiling primitives') -----
  createCPICData: cPIC
  	"Answer an Array of the PIC's selector, followed by class and targetMethod/doesNotUnderstand: for each entry in the PIC."
  	<var: #cPIC type: #'CogMethod *'>
  	| picData |
  	<var: #targetMethod type: #'CogMethod *'>
  	self assert: (cPIC methodObject = 0 or: [objectMemory addressCouldBeOop: cPIC methodObject]).
  	picData := objectMemory instantiateClass: objectMemory classArray indexableSize: cPIC cPICNumCases * 2 + 1.
  	picData ifNil: [^picData].
        objectMemory storePointerUnchecked: 0 ofObject: picData withValue: cPIC selector.
  	1 to: cPIC cPICNumCases do:
  		[:i| | pc entryPoint target targetMethod class |
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		i = 1
  			ifTrue:
  				[class := cPIC methodObject. "first case may have been collected and stored here by collectCogConstituentFor:Annotation:Mcpc:Bcpc:Method:"
  				 class = 0 ifTrue: [class := objectMemory nilObject]. "cPIC is unreferenced; likely evolved to OpenPIC"
  				 entryPoint := backEnd jumpLongTargetBeforeFollowingAddress: pc]
  			ifFalse:
  				[class := objectRepresentation classForInlineCacheTag:
  							(backEnd literal32BeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize).
  				 entryPoint := backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
  		(cPIC containsAddress: entryPoint)
  			ifTrue:
  				[target := objectMemory splObj: SelectorDoesNotUnderstand]
  			ifFalse:
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				 self assert: targetMethod isCMMethodEtAl.
- 				 self assert: targetMethod cmType = CMMethod.
  				 target := targetMethod methodObject].
  		objectMemory
  			storePointerUnchecked: i * 2 - 1 ofObject: picData withValue: class;
  			storePointerUnchecked: i * 2 ofObject: picData withValue: target].
  	objectMemory beRootIfOld: picData.
  	cPIC methodObject: 0. "restore invariant."
  	^picData!

Item was changed:
  ----- Method: Cogit>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
  	| cogMethod mapEntries codeRanges |
  	cogMethod := surrogateOrAddress isInteger
  								ifTrue: [self cogMethodSurrogateAt: surrogateOrAddress]
  								ifFalse: [surrogateOrAddress].
+ 	cogMethod isCMBlock ifTrue:
- 	cogMethod cmType = CMBlock ifTrue:
  		[^self disassembleMethod: cogMethod cmHomeMethod on: aStream].
  	disassemblingMethod ifNil:
  		[^[disassemblingMethod := cogMethod.
  		     self disassembleMethod: surrogateOrAddress on: aStream] ensure:
  			[disassemblingMethod := nil]].
  	self printMethodHeader: cogMethod on: aStream.
  
  	mapEntries := Dictionary new.
  	
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[cogMethod cmIsFullBlock
  			ifTrue:
  				[mapEntries
  					at: cogMethod asInteger + cbNoSwitchEntryOffset put: 'noSwitchEntry';
  					at: cogMethod asInteger + cbEntryOffset put: 'entry']
  			ifFalse:
  				[mapEntries
  					at: cogMethod asInteger + cmNoCheckEntryOffset put: 'noCheckEntry';
  					at: cogMethod asInteger + cmEntryOffset put: 'entry']].
  
+ 	cogMethod isCMClosedPIC
- 	cogMethod cmType = CMClosedPIC
  		ifTrue: "Since Tim R's lovely work on Closed PICs, PIC cases go backwards..."
  			[mapEntries at: cogMethod asInteger + firstCPICCaseOffset put: 'ClosedPICCase', MaxCPICCases printString.
  			 1 to: MaxCPICCases - 1 do:
  				[:i|
  				mapEntries
  					at: cogMethod asInteger + firstCPICCaseOffset + (i * cPICCaseSize)
  					put: 'ClosedPICCase', (MaxCPICCases - i) printString]]
  		ifFalse:
  			[self mapFor: cogMethod
  				performUntil: #collectMapEntry:address:into:
  				arg: mapEntries].
  
  	NewspeakVM ifTrue:
  		[objectRepresentation canPinObjects ifFalse:
  			[mapEntries keys do:
  				[:a|
  				(mapEntries at: a) = #IsNSSendCall ifTrue:
  					[mapEntries
  						at: a + backEnd jumpShortByteSize
  							put: {'Class'. #disassembleCachedOop:. (objectMemory wordSize)};
  						at: a + backEnd jumpShortByteSize + objectMemory bytesPerOop
  							put: {'ImplicitReceiver'. #disassembleCachedOop:. (objectMemory wordSize)}]]]].
  
  	"This would all be far more elegant and simple if we used blocks.
  	 But there are no blocks in C and the basic enumerators here need
  	 to be used in the real VM.  Apologies."
  	(codeRanges := self codeRangesFor: cogMethod) do:
  		[:range|
+ 		(cogMethod isCMMethodEtAl) ifTrue:
- 		(cogMethod cmType = CMMethod) ifTrue:
  			[mapEntries keysAndValuesDo:
  				[:mcpc :label| | bcpc selectorOrNone |
  				(((range includes: mcpc) or: [range last + 1 = mcpc])
  				 and: [(AnnotationsWithBytecodePCs includes: label)
  				 and: [range cogMethod stackCheckOffset > 0]]) ifTrue:
  					[bcpc := self bytecodePCFor: mcpc startBcpc: range startpc in: range cogMethod.
  					 bcpc ~= 0 ifTrue:
  						[label = #IsSendCall
  							ifTrue:
  								[selectorOrNone := (self selectorForSendAt: mcpc annotation: IsSendCall in: cogMethod methodObject).
  								 (selectorOrNone isInteger and: [objectMemory addressCouldBeOop: selectorOrNone]) ifTrue:
  									[selectorOrNone := objectMemory stringOf: selectorOrNone].
  								selectorOrNone := ' ', selectorOrNone]
  							ifFalse: [selectorOrNone := ''].
  						 mapEntries
  							at: mcpc
  							put: label, selectorOrNone, ' bc ', bcpc printString, '/', (bcpc + 1) printString]]]].
  		(cogMethod blockEntryOffset ~= 0
  		 and: [range first = (cogMethod blockEntryOffset + cogMethod asInteger)])
  			ifTrue:
  				[aStream nextPutAll: 'blockEntry:'; cr.
  				 self blockDispatchFor: cogMethod
  					perform: #disassemble:from:to:arg:
  					arg: aStream]
  			ifFalse:
  				[range first > (cogMethod address + cmNoCheckEntryOffset) ifTrue:
  					[self printMethodHeader: range cogMethod
  						on: aStream].
  				self maybeNoteStartpcFor: range.
  				self disassembleFrom: range first to: range last labels: mapEntries on: aStream]].
  	aStream nextPutAll: 'startpc: '; print: codeRanges first startpc; cr.
+ 	(cogMethod isCMMethodEtAl
+ 	 or: [cogMethod isCMOpenPIC]) ifTrue:
- 	(cogMethod cmType = CMMethod
- 	 or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  		[[self mapFor: cogMethod
  			performUntil: #printMapEntry:mcpc:args:
  			arg: { aStream. codeRanges. cogMethod }]
  			on: AssertionFailure
  			do: [:ex|
  				ex primitiveChangeClassTo: ResumableVMError basicNew. ":) :) :)"
  				ex resume: nil]].
  	^cogMethod!

Item was changed:
  ----- Method: Cogit>>entryPointTagIsSelector: (in category 'in-line cacheing') -----
  entryPointTagIsSelector: entryPoint
  	"Answer if the entryPoint's tag is expected to be a selector reference, as opposed to a class tag."
  	^entryPoint < methodZoneBase
  	 or: [(entryPoint bitAnd: entryPointMask) = uncheckedEntryAlignment
  	 or: [(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 		and: [(self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *') isCMOpenPIC]]]!
- 		and: [(self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *') cmType = CMOpenPIC]]]!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	"Fill in the header for the ClosedPIC pic.  This may be located at the writable mapping."
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: closedPICSize.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: false.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
+ 	self assert: pic isCMClosedPIC.
- 	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
  	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
  	self maybeEnableSingleStep
  	"No simulateDualCodeZoneWriteFor:; we do all the simulated copying in the sender..."!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	"Fill in the header for the OpenPIC pic.  This may be located at the writable mapping."
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector).
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  
  	"This also implicitly flushes the read/write mapped dual zone to the read/execute zone."
  	backEnd flushICacheFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
  
+ 	self assert: pic isCMOpenPIC.
- 	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger - codeToDataDelta + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
  	self assertValidDualZoneFrom: pic asUnsignedInteger - codeToDataDelta to: pic asUnsignedInteger - codeToDataDelta + openPICSize.
  	self maybeEnableSingleStep!

Item was changed:
  ----- Method: Cogit>>findMethodForStartBcpc:inHomeMethod: (in category 'method map') -----
  findMethodForStartBcpc: startbcpc inHomeMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<returnTypeC: #'CogBlockMethod *'>
  	"Find the CMMethod or CMBlock that has zero-relative startbcpc as its first bytecode pc.
  	 As this is for cannot resume processing and/or conversion to machine-code on backward
  	 branch, it doesn't have to be fast.  Enumerate block returns and map to bytecode pcs."
+ 	self assert: cogMethod isCMMethodEtAl.
- 	self assert: cogMethod cmType = CMMethod.
  	startbcpc = (coInterpreter startPCOfMethodHeader: cogMethod methodHeader) ifTrue:
  		[^self cCoerceSimple: cogMethod to: #'CogBlockMethod *'].
  	self assert: cogMethod blockEntryOffset ~= 0.
  	^self cCoerceSimple: (self blockDispatchTargetsFor: cogMethod
  								perform: #findBlockMethodWithEntry:startBcpc:
  								arg: startbcpc)
  		to: #'CogBlockMethod *'!

Item was changed:
  ----- Method: Cogit>>firstMappedPCFor: (in category 'method map') -----
  firstMappedPCFor: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
+ 	^(cogMethod isCMMethodEtAl and: [cogMethod cmIsFullBlock])
- 	^(cogMethod cmType < CMClosedPIC and: [cogMethod cmIsFullBlock])
  		ifTrue: [cogMethod asUnsignedInteger + cbNoSwitchEntryOffset]
  		ifFalse: [cogMethod asUnsignedInteger + cmNoCheckEntryOffset]!

Item was changed:
  ----- 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') -----
  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') -----
  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 not ifTrue:
- 		[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 changed:
  ----- Method: Cogit>>freePICsWithFreedTargets (in category 'compaction') -----
  freePICsWithFreedTargets
  	| cogMethod count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	count := 0.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMClosedPIC
+ 		  and: [self cPICHasFreedTargets: cogMethod]) ifTrue:
+ 			[(self writableMethodFor: cogMethod) cmType: CMFree].
- 		[(cogMethod cmType = CMClosedPIC
- 		 and: [self cPICHasFreedTargets: cogMethod]) ifTrue:
- 			[cogMethod cmType: CMFree].
  		 cogMethod := methodZone methodAfter: cogMethod.
  		 count := count + 1].
  	self assert: count = methodZone numMethods!

Item was changed:
  ----- Method: Cogit>>freeUnmarkedMachineCode (in category 'jit - api') -----
  freeUnmarkedMachineCode
  	"Free machine-code methods whose compiled methods are unmarked
  	 and open PICs whose selectors are not marked, and closed PICs that
  	 refer to unmarked objects."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod freedMethod |
  	self moveProfileToMethods. "simulation only..."
  
  	freedMethod := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMMethodEtAl
- 		[(cogMethod cmType = CMMethod
  		  and: [(objectMemory isMarked: cogMethod methodObject) not]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
+ 		 (cogMethod isCMOpenPIC
- 		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector) not
  		  and: [(objectMemory isMarked: cogMethod selector) not]]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
+ 		 (cogMethod isCMClosedPIC
- 		 (cogMethod cmType = CMClosedPIC
  		  and: [self closedPICRefersToUnmarkedObject: cogMethod]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedMethod ifTrue:
  		[self unlinkSendsToFree].
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>linkedSuperSendCacheTags (in category 'analysis') -----
  linkedSuperSendCacheTags
  	"An example; answer the cache tags for linked super sends.  They should all be
  	 selectors because super sends don't have their cache tag rewritten when linked."
  	<doNotGenerate>
  	| cacheTags |
  	cacheTags := Set new.
  	methodZone methodsDo:
  		[:m|
+ 		 m isCMMethodEtAl ifTrue:
- 		 m cmType = CMMethod ifTrue:
  			[self sendSitesIn: m do:
  				[:a :mcpc| | entryPoint |
  				 entryPoint := backEnd callTargetFromReturnAddress: mcpc.
  				 entryPoint > methodZoneBase ifTrue:
  					[self offsetAndSendTableFor: entryPoint
  						annotation: a
  						into:
  							[:off :table|
  							 off = cmNoCheckEntryOffset ifTrue:
  								[cacheTags add: (backEnd inlineCacheTagAt: mcpc)]]]]]].
  	^cacheTags!

Item was changed:
  ----- Method: Cogit>>mapFor:bcpc:performUntil:arg: (in category 'method map') -----
  mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
  	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
  	 for each mcpc, bcpc pair in the map until the function returns non-zero,
  	 answering that result, or 0 if it fails to.  To cut down on number of arguments.
  	 and to be usable for both pc-mapping and method introspection, we encode
  	 the annotation and the isBackwardBranch flag in the same parameter.
  	 Guilty as charged."
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(BytecodeDescriptor *desc, sqInt annotationAndIsBackwardBranch, char *mcpc, sqInt bcpc, void *arg)'>
  	<var: #arg type: #'void *'>
  	<inline: true>
  	| isInBlock mcpc bcpc endbcpc map mapByte homeMethod aMethodObj result
  	  latestContinuation byte descriptor bsOffset nExts annotation |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
  	<var: #homeMethod type: #'CogMethod *'>
  
  	self assert: cogMethod stackCheckOffset > 0.
  	mcpc := cogMethod asUnsignedInteger + cogMethod stackCheckOffset.
  	"The stack check maps to the start of the first bytecode,
  	 the first bytecode being effectively after frame build."
  	result := self perform: functionSymbol
  					with: nil
  					with: 0 + (HasBytecodePC << 1)
  					with: (self cCoerceSimple: mcpc to: #'char *')
  					with: startbcpc
  					with: arg.
  	result ~= 0 ifTrue:
  		[^result].
  	bcpc := startbcpc.
  	"In both CMMethod and CMBlock cases find the start of the map and
  	 skip forward to the bytecode pc map entry for the stack check."
+ 	cogMethod isCMMethodEtAl
- 	cogMethod cmType = CMMethod
  		ifTrue:
  			[isInBlock := cogMethod cmIsFullBlock.
  			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
  			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
  			 map := self mapStartFor: homeMethod.
  			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
  			 self assert: (annotation = IsAbsPCReference
  						 or: [annotation = IsObjectReference
  						 or: [annotation = IsRelativeCall
  						 or: [annotation = IsDisplacementX2N]]]).
  			 latestContinuation := startbcpc.
  			 aMethodObj := homeMethod methodObject.
  			 endbcpc := (objectMemory numBytesOf: aMethodObj) - 1.
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			"If the method has a primitive, skip it and the error code store, if any;
  			 Logically. these come before the stack check and so must be ignored."
  			 bcpc := bcpc + (self deltaToSkipPrimAndErrorStoreIn: aMethodObj
  									header: homeMethod methodHeader)]
  		ifFalse:
  			[isInBlock := true.
  			 self assert: bcpc = cogMethod startpc.
  			 homeMethod := cogMethod cmHomeMethod.
  			 map := self findMapLocationForMcpc: cogMethod asUnsignedInteger + (self sizeof: CogBlockMethod)
  						inMethod: homeMethod.
  			 self assert: map ~= 0.
  			 annotation := (objectMemory byteAt: map) >> AnnotationShift.
  			 self assert: (annotation >> AnnotationShift = HasBytecodePC "fiducial"
  						 or: [annotation >> AnnotationShift = IsDisplacementX2N]).
  			 [(annotation := (objectMemory byteAt: map) >> AnnotationShift) ~= HasBytecodePC] whileTrue:
  				[map := map - 1].
  			 map := map - 1. "skip fiducial; i.e. the map entry for the pc immediately following the method header."
  			 aMethodObj := homeMethod methodObject.
  			 bcpc := startbcpc - (self blockCreationBytecodeSizeForHeader: homeMethod methodHeader).
  			 bsOffset := self bytecodeSetOffsetForHeader: homeMethod methodHeader.
  			 byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  			 descriptor := self generatorAt: byte.
  			 endbcpc := self nextBytecodePCFor: descriptor at: bcpc exts: -1 in: aMethodObj.
  			 bcpc := startbcpc].
  	nExts := 0.
  	self inlineCacheTagsAreIndexes ifTrue:
  		[enumeratingCogMethod := homeMethod].
  	"Now skip up through the bytecode pc map entry for the stack check." 
  	[(objectMemory byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
  		[map := map - 1].
  	map := map - 1.
  	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue: "defensive; we exit on bcpc"
  		[mapByte >= FirstAnnotation
  			ifTrue:
  				[| nextBcpc isBackwardBranch |
  				annotation := mapByte >> AnnotationShift.
  				mcpc := mcpc + ((mapByte bitAnd: DisplacementMask) * backEnd codeGranularity).
  				(self isPCMappedAnnotation: annotation) ifTrue:
  					[(annotation = IsSendCall
  					  and: [(mapByte := objectMemory byteAt: map - 1) >> AnnotationShift = IsAnnotationExtension]) ifTrue:
  						[annotation := annotation + (mapByte bitAnd: DisplacementMask).
  						 map := map - 1].
  					 [byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  					  descriptor := self generatorAt: byte.
  					  isInBlock
  						ifTrue: [bcpc >= endbcpc ifTrue: [^0]]
  						ifFalse:
  							[(descriptor isReturn and: [bcpc >= latestContinuation]) ifTrue: [^0].
  							 (descriptor isBranch or: [descriptor isBlockCreation]) ifTrue:
  								[| targetPC |
  								 targetPC := self latestContinuationPCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  								 latestContinuation := latestContinuation max: targetPC].
  							 latestContinuation := self maybeUnsafeJumpContinuation: latestContinuation at: bcpc for: descriptor in: aMethodObj].
  					  nextBcpc := self nextBytecodePCFor: descriptor at: bcpc exts: nExts in: aMethodObj.
  					  descriptor isMapped
  					  or: [isInBlock and: [descriptor isMappedInBlock]]] whileFalse:
  						[bcpc := nextBcpc.
  						 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]].
  					 isBackwardBranch := descriptor isBranch
  										   and: [self isBackwardBranch: descriptor at: bcpc exts: nExts in: aMethodObj].
  					 result := self perform: functionSymbol
  									with: descriptor
  									with: (isBackwardBranch ifTrue: [annotation << 1 + 1] ifFalse: [annotation << 1])
  									with: (self cCoerceSimple: mcpc to: #'char *')
  									with: (isBackwardBranch ifTrue: [bcpc - (2 * nExts)] ifFalse: [bcpc])
  									with: arg.
  					 result ~= 0 ifTrue:
  						[^result].
  					 bcpc := nextBcpc.
  					 nExts := descriptor isExtension ifTrue: [nExts + 1] ifFalse: [0]]]
  			ifFalse:
  				[self assert: (mapByte >> AnnotationShift = IsDisplacementX2N
  							or: [mapByte >> AnnotationShift = IsAnnotationExtension]).
  				 mapByte < (IsAnnotationExtension << AnnotationShift) ifTrue:
  					[mcpc := mcpc + ((mapByte - DisplacementX2N << AnnotationShift) * backEnd codeGranularity)]].
  		 map := map - 1].
  	^0!

Item was changed:
  ----- 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') -----
  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') -----
  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') -----
  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>>markAndTraceMachineCodeForNewSpaceGC (in category 'jit - api') -----
  markAndTraceMachineCodeForNewSpaceGC
  	"Free any methods that refer to unmarked objects, unlinking sends to freed methods."
  	| pointer cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckNewSpaceGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
+ 			 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 ifTrue:
- 			 cogMethod cmType = CMMethod ifTrue:
  				[(objectMemory isYoung: cogMethod methodObject) ifTrue:
  					[objectMemory markAndTrace: cogMethod methodObject].
  				self markYoungObjectsIn: cogMethod]].
  		 pointer := pointer + objectMemory wordSize].
  	objectMemory leakCheckNewSpaceGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	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>>markAndTraceMachineCodeOfMarkedMethods (in category 'jit - api') -----
  markAndTraceMachineCodeOfMarkedMethods
  	"Mark objects in machine-code of marked methods (or open PICs with marked selectors)."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	self markAndTraceObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMMethodEtAl
- 		[(cogMethod cmType = CMMethod
  		  and: [objectMemory isMarked: cogMethod methodObject]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
+ 		 (cogMethod isCMOpenPIC
- 		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector)
  				or: [objectMemory isMarked: cogMethod selector]]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	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>>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') -----
  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') -----
  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>>markMethodAndReferents: (in category 'jit - api') -----
  markMethodAndReferents: aCogMethod
  	<api>
  	<var: #aCogMethod type: #'CogBlockMethod *'>
  	| cogMethod writableMethod |
+ 	self assert: (aCogMethod isCMMethodEtAl
+ 				or: [aCogMethod isCMBlock]).
+ 	cogMethod := aCogMethod isCMMethodEtAl
- 	self assert: (aCogMethod cmType = CMMethod
- 				or: [aCogMethod cmType = CMBlock]).
- 	cogMethod := aCogMethod cmType = CMMethod
  					ifTrue: [self cCoerceSimple: aCogMethod to: #'CogMethod *']
  					ifFalse: [aCogMethod cmHomeMethod].
  	writableMethod := self writableMethodFor: cogMethod.
  	writableMethod cmUsageCount: CMMaxUsageCount.
  	self mapFor: cogMethod
  		performUntil: #incrementUsageOfTargetIfLinkedSend:mcpc:ignored:
  		arg: 0!

Item was changed:
  ----- 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 changed:
  ----- Method: Cogit>>moveProfileToMethods (in category 'analysis') -----
  moveProfileToMethods
  	"Simulation only counting of instructions per method/pic/trampoline..."
  	<cmacro: '() 0'>
  	"Whenever a change in the code zone is about to occur (e.g. compact code zone, free a method)
  	 move all counts to the corresponding Smalltalk objects."
  	perMethodProfile ifNotNil:
  		[:pmp|
  		0 to: trampolineTableIndex - 3 by: 2 do:
  			[:i| | trampoline total |
  			total := 0.
  			trampoline := trampolineAddresses at: i + 1.
  			trampoline to: (trampolineAddresses at: i + 3) - 1 do:
  				[:pc| total := total + (instructionProfile at: pc)].
  			total > 0 ifTrue:
  				[perMethodProfile at: trampoline put: (perMethodProfile at: trampoline ifAbsent: 0) + total]].
  		methodZone methodsDo:
  			[:cogMethod| | total |
  			total := 0.
  			cogMethod + 1 to: cogMethod address + cogMethod blockSize do:
  				[:pc| total := total + (instructionProfile at: pc)].
  			total > 0 ifTrue:
+ 				[(cogMethod isCMMethodEtAl
- 				[(cogMethod cmType = CMMethod
  					ifTrue: [cogMethod methodObject]
  					ifFalse:
+ 						[(cogMethod isCMClosedPIC
+ 						  or: [cogMethod isCMOpenPIC]) ifTrue:
- 						[(cogMethod cmType = CMClosedPIC
- 						  or: [cogMethod cmType = CMOpenPIC]) ifTrue:
  							[cogMethod selector]]) ifNotNil:
  					[:thang|
  					perMethodProfile at: thang put: (perMethodProfile at: thang ifAbsent: 0) + total]]].
  		instructionProfile atAllPut: 0]!

Item was changed:
  ----- Method: Cogit>>noCogMethodsMaximallyMarked (in category 'compaction') -----
  noCogMethodsMaximallyMarked
  	"Check that no method is maximally marked.  A maximal mark is an indication the
  	 method has been scanned to increase the usage count of its referent methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[(cogMethod isCMFree not
- 		[(cogMethod cmType ~= CMFree
  		  and: [cogMethod cmUsageCount = CMMaxUsageCount]) ifTrue:
  			[^false].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	^true!

Item was changed:
  ----- Method: Cogit>>printMethodHeader:on: (in category 'disassembly') -----
  printMethodHeader: cogMethod on: aStream
  	<doNotGenerate>
  	self cCode: ''
  		inSmalltalk:
  			[cogMethod isInteger ifTrue:
  				[^self printMethodHeader: (self cogMethodOrBlockSurrogateAt: cogMethod) on: aStream]].
  	aStream ensureCr.
  	cogMethod asInteger printOn: aStream base: 16.
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[aStream crtab; nextPutAll: 'objhdr: '.
  		cogMethod objectHeader printOn: aStream base: 16].
+ 	cogMethod isCMBlock ifTrue:
- 	cogMethod cmType = CMBlock ifTrue:
  		[aStream crtab; nextPutAll: 'homemth: '.
  		cogMethod cmHomeMethod asUnsignedInteger printOn: aStream base: 16.
  		aStream
  			nextPutAll: ' (offset '; print: cogMethod homeOffset; nextPut: $);
  			crtab; nextPutAll: 'startpc: '; print: cogMethod startpc].
  	aStream
  		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
  		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
+ 	(cogMethod cmType ~= 0 and: [cogMethod isCMBlock]) ifTrue:
- 	(cogMethod cmType ~= 0 and: [cogMethod cmType ~= CMBlock]) ifTrue:
  		[aStream crtab; nextPutAll: 'blksiz: '.
  		cogMethod blockSize printOn: aStream base: 16.
+ 		cogMethod isCMMethodEtAl ifTrue:
- 		cogMethod cmType = CMMethod ifTrue:
  			[aStream crtab; nextPutAll: 'method: '.
  			 cogMethod methodObject printOn: aStream base: 16.
  			 aStream crtab; nextPutAll: 'mthhdr: '.
  			 cogMethod methodHeader printOn: aStream base: 16].
  		aStream crtab; nextPutAll: 'selctr: '.
  		cogMethod selector printOn: aStream base: 16.
  		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
  			[:string| aStream nextPut: $=; nextPutAll: string].
  		cogMethod selector = objectMemory nilObject ifTrue:
  			[aStream space; nextPut: $(; nextPutAll: (coInterpreter stringOf: (coInterpreter maybeSelectorOfMethod: cogMethod methodObject)); nextPut: $)]. 
+ 		cogMethod isCMMethodEtAl ifTrue:
- 		cogMethod cmType = CMMethod ifTrue:
  			[aStream crtab; nextPutAll: 'blkentry: '.
  			 cogMethod blockEntryOffset printOn: aStream base: 16.
  			 cogMethod blockEntryOffset ~= 0 ifTrue:
  				[aStream nextPutAll: ' => '.
  				 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]]].
+ 	cogMethod isCMClosedPIC
- 	cogMethod cmType = CMClosedPIC
  		ifTrue:
  			[aStream crtab; nextPutAll: 'cPICNumCases: '.
  			 cogMethod cPICNumCases printOn: aStream base: 16.
  			 aStream tab; nextPutAll: 'cpicHasMNUCase: ';
  			 nextPutAll: (cogMethod cpicHasMNUCase ifTrue: ['yes'] ifFalse: ['no'])]
  		ifFalse:
  			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
  			 cogMethod stackCheckOffset printOn: aStream base: 16.
  			 cogMethod stackCheckOffset > 0 ifTrue:
  				[aStream nextPut: $/.
  				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16].
+ 			cogMethod isCMBlock
- 			cogMethod cmType = CMBlock
  				ifTrue:
  					[aStream
  						crtab;
  						nextPutAll: 'cbUsesInstVars ';
  						nextPutAll: (cogMethod cbUsesInstVars ifTrue: ['yes'] ifFalse: ['no'])]
  				ifFalse:
  					[aStream
  						crtab;
  						nextPutAll: 'cmRefersToYoung: ';
  						nextPutAll: (cogMethod cmRefersToYoung ifTrue: ['yes'] ifFalse: ['no']);
  						tab;
  						nextPutAll: 'cmHasMovableLiteral: ';
  						nextPutAll: (cogMethod cmHasMovableLiteral ifTrue: ['yes'] ifFalse: ['no']);
  						tab;
  						nextPutAll: 'cmIsFullBlock: ';
  						nextPutAll: (cogMethod cmIsFullBlock ifTrue: ['yes'] ifFalse: ['no'])].
+ 			cogMethod isCMMethodEtAl ifTrue:
- 			cogMethod cmType = CMMethod ifTrue:
  				[([cogMethod nextMethodOrIRCs] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:nmoircs| aStream crtab; nextPutAll: 'nextMethodOrIRCs: '.
  						nmoircs = 0 ifTrue: [aStream print: nmoircs] ifFalse: [coInterpreter printHex: nmoircs]].
  				 ([cogMethod counters] on: MessageNotUnderstood do: [:ex| nil]) ifNotNil:
  					[:cntrs| aStream crtab; nextPutAll: 'counters: '.
  						cntrs = 0 ifTrue: [aStream print: cntrs] ifFalse: [coInterpreter printHex: cntrs]]]].
  	aStream cr; flush!

Item was changed:
  ----- Method: Cogit>>profileDataFor:withDetails: (in category 'profiling primitives') -----
  profileDataFor: cogMethod withDetails: withDetails
  	"Answers characteristic data for the type of the cogMethod, answering
  		a CompiledMethod for a compiled method,
  		a selector for an open PIC
  		if withDetails then an array containing a selector followed by pairs of class and target method for a closed PIC, otherwise simply a selector."
  	<inline: true>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	^cogMethod isCMMethodEtAl 
- 	^cogMethod cmType = CMMethod 
  		ifTrue: [cogMethod methodObject]
+ 		ifFalse: [(withDetails and: [cogMethod isCMClosedPIC])
- 		ifFalse: [(withDetails and: [cogMethod cmType = CMClosedPIC])
  					ifTrue: [self createCPICData: cogMethod]
  					ifFalse: [cogMethod selector]]!

Item was changed:
  ----- Method: Cogit>>relocateCallsAndSelfReferencesInMethod: (in category 'compaction') -----
  relocateCallsAndSelfReferencesInMethod: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
  	| refDelta callDelta |
  	refDelta := cogMethod objectHeader.
  	callDelta := backEnd zoneCallsAreRelative ifTrue: [refDelta] ifFalse: [0].
  	
+ 	self assert: (cogMethod isCMMethodEtAl or: [cogMethod isCMOpenPIC]).
- 	self assert: (cogMethod cmType = CMMethod or: [cogMethod cmType = CMOpenPIC]).
  	self assert: (backEnd callTargetFromReturnAddress: cogMethod asInteger + missOffset)
+ 				= (cogMethod isCMMethodEtAl
- 				= (cogMethod cmType = CMMethod
  					ifTrue: [self methodAbortTrampolineFor: cogMethod cmNumArgs]
  					ifFalse: [self picAbortTrampolineFor: cogMethod cmNumArgs]).
  	backEnd relocateCallBeforeReturnPC: cogMethod asInteger + missOffset by: callDelta negated.
  	self mapFor: cogMethod
  		performUntil: #relocateIfCallOrMethodReference:mcpc:delta:
  		arg: refDelta asVoidPointer!

Item was changed:
  ----- Method: Cogit>>relocateCallsInClosedPIC: (in category 'compaction') -----
  relocateCallsInClosedPIC: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| refDelta callDelta pc entryPoint targetMethod |
  	<var: #targetMethod type: #'CogMethod *'>
  	refDelta := cPIC objectHeader.
  	callDelta := backEnd zoneCallsAreRelative ifTrue: [refDelta] ifFalse: [0].
  	
  	self assert: (backEnd callTargetFromReturnAddress: cPIC asInteger + missOffset)
  					= (self picAbortTrampolineFor: cPIC cmNumArgs).
  	backEnd relocateCallBeforeReturnPC: cPIC asInteger + missOffset by: callDelta negated.
  
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		(cPIC containsAddress: entryPoint) 
  			ifTrue: 
  			["Interpret/MNU"
  			backEnd zoneCallsAreRelative ifFalse: [
  				i = 1 ifTrue:
  					[backEnd
  						relocateJumpLongBeforeFollowingAddress: pc
  						by: refDelta]
  					ifFalse:
  					[backEnd
  						relocateJumpLongConditionalBeforeFollowingAddress: pc
  						by: refDelta]]]
  			ifFalse:
  			[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 			 self assert: targetMethod isCMMethodEtAl.
- 			 self assert: targetMethod cmType = CMMethod.
  			 i = 1 ifTrue:
  				[backEnd
  					relocateJumpLongBeforeFollowingAddress: pc
  					by: (callDelta - targetMethod objectHeader) negated]
  				ifFalse:
  				[backEnd
  					relocateJumpLongConditionalBeforeFollowingAddress: pc
  					by: (callDelta - targetMethod objectHeader) negated]]].
  	self assert: cPIC cPICNumCases > 0.
  
  	"Finally relocate the load of the PIC and the jump to the overflow routine ceCPICMiss:receiver:"
  	backEnd relocateMethodReferenceBeforeAddress: (self addressOfEndOfCase: 2 inCPIC: cPIC)+ backEnd loadPICLiteralByteSize by: refDelta.
  	backEnd relocateJumpLongBeforeFollowingAddress: cPIC asInteger + cPICEndOfCodeOffset by: callDelta negated!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: refDeltaArg
  	<var: #mcpc type: #'char *'>
  	<var: #refDeltaArg type: #'CogMethod *'> "To placate the C static type system..."
  	| refDelta callDelta entryPoint targetMethod unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
  	refDelta := self cCoerceSimple: refDeltaArg to: #sqInt.
  	callDelta := backEnd zoneCallsAreRelative ifTrue: [refDelta] ifFalse: [0].
  	
  	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				targetMethod isCMMethodEtAl
- 				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
  						[self voidNSSendCache: nsSendCache]].
  			^0]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:offset :sendTable|
  				 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 				 targetMethod isCMFree not ifTrue: "send target not freed; just relocate."
- 				 targetMethod cmType ~= CMFree ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (callDelta - targetMethod objectHeader) negated.
  					 SistaVM ifTrue: "See comment in planCompaction"
  						[methodZone restorePICUsageCount: targetMethod].
  					 ^0].
  				 "Target was freed; map back to an unlinked send; but include this method's reocation"
  				 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  				 unlinkedRoutine := unlinkedRoutine - callDelta.
  				 backEnd
  					rewriteInlineCacheAt: mcpc asInteger
  					tag: (backEnd inlineCacheValueForSelector: targetMethod selector in: enumeratingCogMethod)
  					target: unlinkedRoutine.
  				 ^0]].
  
  	annotation = IsRelativeCall ifTrue:
  		[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: callDelta negated.
  		 ^0].
  
  	annotation = IsAbsPCReference ifTrue:
  		[backEnd relocateMethodReferenceBeforeAddress: mcpc asInteger by: refDelta].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>setSelectorOf:to: (in category 'jit - api') -----
  setSelectorOf: cogMethod to: aSelectorOop
  	<api>
  	"If a method is compiled to machine code via a block entry it won't have a selector.
  	 A subsequent send can find the method and hence fill in the selector."
  	<var: #cogMethod type: #'CogMethod *'>
  	"self disassembleMethod: cogMethod"
  	coInterpreter compilationBreakpoint: aSelectorOop isMNUCase: false.
+ 	self assert: cogMethod isCMMethodEtAl.
- 	self assert: cogMethod cmType = CMMethod.
  	self ensureWritableCodeZone.
  	(self writableMethodFor: cogMethod) selector: aSelectorOop.
  	(objectMemory isYoung: aSelectorOop) ifTrue:
  		[methodZone ensureInYoungReferrers: cogMethod].
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>subMethodsAsRangesFor: (in category 'method map') -----
  subMethodsAsRangesFor: surrogateOrAddress
  	<doNotGenerate>
  	| cogMethod codeRanges |
  	cogMethod := surrogateOrAddress isInteger
  								ifTrue: [self cogMethodSurrogateAt: surrogateOrAddress]
  								ifFalse: [surrogateOrAddress].
+ 	^cogMethod isCMMethodEtAl ifTrue:
- 	^cogMethod cmType = CMMethod ifTrue:
  		[codeRanges := self codeRangesFor: cogMethod.
  		 ^codeRanges size > 1 "omit the block dispatch range"
  			ifTrue: [codeRanges allButLast]
  			ifFalse: [codeRanges]]!

Item was changed:
  ----- Method: Cogit>>unlinkAllSends (in category 'jit - api') -----
  unlinkAllSends
  	<api>
  	"Unlink all sends in cog methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	self ensureWritableCodeZone.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	methodZone voidOpenPICList.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl
- 		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:ignored:
  					 arg: 0]
  			ifFalse:
+ 				[cogMethod isCMFree ifFalse:
- 				[cogMethod cmType ~= CMFree ifTrue:
  					[methodZone freeMethod: cogMethod]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"After updating inline caches we need to flush the icache."
  	backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart!

Item was changed:
  ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	<var: #theSelector type: #'CogMethod *'> "To placate the C static type system..."
  
- 	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
+ 	<var: #nsSendCache type: #'NSSendCache *'>
  
  	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				(targetMethod isCMFree
- 				(targetMethod cmType = CMFree
  				 or: [nsSendCache selector = (self cCoerceSimple: theSelector to: #sqInt)]) ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
+ 					 (targetMethod isCMFree
- 					 (targetMethod cmType = CMFree
  					  or: [targetMethod selector = (self cCoerceSimple: theSelector to: #sqInt)]) ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfInvalidClassSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfInvalidClassSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
  	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (nsSendCache classTag ~= objectRepresentation illegalClassTag
  			  and: [objectMemory isForwardedClassIndex: nsSendCache classTag]) ifTrue:
  				[self voidNSSendCache: nsSendCache]].
  			"Should we check if the enclosing object's class is forwarded as well?"
  			^0 "keep scanning"].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable|
  				 ((self annotationIsForUncheckedEntryPoint: annotation)
+ 				  or: [targetMethod isCMOpenPIC]) ifFalse:
- 				  or: [targetMethod cmType = CMOpenPIC]) ifFalse:
  					[(objectMemory isValidClassTag: (backEnd inlineCacheTagAt: mcpc asInteger)) ifFalse:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSendToFree:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSendToFree: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
+ 	| entryPoint |
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #nsTargetMethod type: #'CogMethod *'>
- 	| entryPoint |
  
  	NewspeakVM ifTrue:
  		[| nsSendCache nsTargetMethod |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue: "It's a linked send."
  				[nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				nsTargetMethod isCMFree ifTrue:
- 				nsTargetMethod cmType = CMFree ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable| 
+ 				 targetMethod isCMFree ifTrue:
- 				 targetMethod cmType = CMFree ifTrue:
  					[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

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

Item was changed:
  ----- Method: Cogit>>unlinkSendsOf:isMNUSelector: (in category 'jit - api') -----
  unlinkSendsOf: selector isMNUSelector: isMNUSelector
  	<api>
  	"Unlink all sends in cog methods. Free all Closed PICs with the selector,
  	 or with an MNU case if isMNUSelector.  First check if any method actually
  	 has the selector; if not there can't be any linked send to it.  This routine
  	 (including descendents) is performance critical.  It contributes perhaps
  	 30% of entire execution time in Compiler recompileAll."
  	| cogMethod mustScanAndUnlink |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	mustScanAndUnlink := false.
  	isMNUSelector
  		ifTrue:
  			[[cogMethod < methodZone limitZony] whileTrue:
+ 				[cogMethod isCMFree ifFalse:
- 				[cogMethod cmType ~= CMFree ifTrue:
  					[cogMethod cpicHasMNUCase
  						ifTrue:
+ 							[self assert: cogMethod isCMClosedPIC.
- 							[self assert: cogMethod cmType = CMClosedPIC.
  							 methodZone freeMethod: cogMethod.
  							 mustScanAndUnlink := true]
  						ifFalse:
  							[cogMethod selector = selector ifTrue:
  								[mustScanAndUnlink := true.
+ 								 cogMethod isCMClosedPIC ifTrue:
- 								 cogMethod cmType = CMClosedPIC ifTrue:
  									[methodZone freeMethod: cogMethod]]]].
  				 cogMethod := methodZone methodAfter: cogMethod]]
  		ifFalse:
  			[[cogMethod < methodZone limitZony] whileTrue:
+ 				[(cogMethod isCMFree not
- 				[(cogMethod cmType ~= CMFree
  				  and: [cogMethod selector = selector]) ifTrue:
  					[mustScanAndUnlink := true.
+ 					 cogMethod isCMClosedPIC ifTrue:
- 					 cogMethod cmType = CMClosedPIC ifTrue:
  						[methodZone freeMethod: cogMethod]].
  				 cogMethod := methodZone methodAfter: cogMethod]].
  	mustScanAndUnlink ifFalse:
  		[^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl ifTrue:
- 		[cogMethod cmType = CMMethod ifTrue:
  			[self mapFor: cogMethod
  				 performUntil: #unlinkIfFreeOrLinkedSend:pc:of:
  				 arg: (self cCoerceSimple: selector to: #'CogMethod *')].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart].
  	"And ensure code zone is executable.  May merely have freed methods..."
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>unlinkSendsTo:andFreeIf: (in category 'jit - api') -----
  unlinkSendsTo: targetMethodObject andFreeIf: freeIfTrue
  	<api>
  	"Unlink all sends in cog methods to a particular target method.
  	 If targetMethodObject isn't actually a method (perhaps being
  	 used via invokeAsMethod) then there's nothing to do."
  	| cogMethod targetMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	((objectMemory isOopCompiledMethod: targetMethodObject)
  	and: [coInterpreter methodHasCogMethod: targetMethodObject]) ifFalse:
  		[^self].
  	targetMethod := coInterpreter cogMethodOf: targetMethodObject.
  	methodZoneBase ifNil: [^self].
  	self ensureWritableCodeZone.
  	codeModified := freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl
- 		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:to:
  					 arg: targetMethod]
  			ifFalse:
+ 				[(cogMethod isCMClosedPIC
- 				[(cogMethod cmType = CMClosedPIC
  				  and: [self cPIC: cogMethod HasTarget: targetMethod]) ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedPIC := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freeIfTrue ifTrue: [self freeMethod: targetMethod].
  	freedPIC
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  				[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart]].
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: Cogit>>unlinkSendsToFree (in category 'jit - api') -----
  unlinkSendsToFree
  	<api>
  	"Unlink all sends in cog methods to free methods and/or pics."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl
- 		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSendToFree:pc:ignored:
  					 arg: 0]
  			ifFalse:
+ 				[cogMethod isCMClosedPIC ifTrue:
- 				[cogMethod cmType = CMClosedPIC ifTrue:
  					[self assert: (self noTargetsFreeInClosedPIC: cogMethod)]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsToMethodsSuchThat:AndFreeIf: (in category 'jit - api') -----
  unlinkSendsToMethodsSuchThat: criterion AndFreeIf: freeIfTrue
  	<api>
  	"Unlink all sends in cog methods to methods with a machine code
  	 primitive, and free machine code primitive methods if freeIfTrue.
  	 To avoid having to scan PICs, free any and all PICs"
  	<var: 'criterion' declareC: 'sqInt (*criterion)(CogMethod *)'>
  	| cogMethod freedSomething |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	self cCode: nil inSmalltalk: [debugAPISelector := nil].
  	codeModified := freedSomething := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
+ 		[cogMethod isCMMethodEtAl
- 		[cogMethod cmType = CMMethod
  			ifTrue:
  				[(freeIfTrue
  				  and: [self perform: criterion with: cogMethod])
  					ifTrue:
  						[methodZone freeMethod: cogMethod.
  						 freedSomething := true]
  					ifFalse:
  						[self mapFor: cogMethod
  							 performUntil: #unlinkIfLinkedSend:pc:if:
  							 arg: criterion]]
  			ifFalse:
+ 				[cogMethod isCMClosedPIC ifTrue:
- 				[cogMethod cmType = CMClosedPIC ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedSomething := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freedSomething
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  				[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone freeStart]].
  	self ensureExecutableCodeZone!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>printCogMethod: (in category 'printing') -----
  printCogMethod: cogMethod
  	| address primitive |
  	address := cogMethod asInteger.
  	self printHex: address;
  		print: ' <-> ';
  		printHex: address + cogMethod blockSize.
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[self print: ': method: ';
  			printHex: cogMethod methodObject.
  		 primitive := self primitiveIndexOfMethod: cogMethod methodObject
  							header: cogMethod methodHeader.
  		 primitive ~= 0 ifTrue:
  			[self print: ' prim '; printNum: primitive]].
+ 	cogMethod isCMBlock ifTrue:
- 	cogMethod cmType = CMBlock ifTrue:
  		[self print: ': block home: ';
  			printHex: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod asUnsignedInteger].
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[self print: ': Closed PIC N: ';
  			printHex: cogMethod cPICNumCases].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[self print: ': Open PIC '].
  	self print: ' selector: '; printHex: cogMethod selector.
  	cogMethod selector = objectMemory nilObject
  		ifTrue: [self print: ' (nil)']
  		ifFalse: [self space; printStringOf: cogMethod selector].
  	self cr!

Item was changed:
  ----- Method: SistaCogit>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
  	| cogMethod |
  	cogMethod := super disassembleMethod: surrogateOrAddress on: aStream.
+ 	(cogMethod isCMMethodEtAl
- 	(cogMethod cmType = CMMethod
  	 and: [cogMethod counters ~= 0]) ifTrue:
  		[aStream nextPutAll: 'counters:'; cr.
  		 0 to: (objectRepresentation numCountersFor: cogMethod counters) - 1 do:
  			[:i| | addr |
  			 addr := i * CounterBytes + counters.
  			 addr printOn: aStream base: 16.
  			 aStream nextPut: $:; space.
  			 (objectMemory long32At: addr) printOn: aStream base: 16.
  			 aStream cr].
  		 aStream flush]!

Item was changed:
  ----- Method: SistaCogit>>picDataForSendTo:methodClassIfSuper:at:bcpc: (in category 'method introspection') -----
  picDataForSendTo: cogMethod methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc
  	"Answer a tuple with the send data for a linked send to cogMethod.
  	 If the target is a CogMethod (monomorphic send) answer
  		{ bytecode pc, inline cache class, target method }
  	 If the target is an open PIC (megamorphic send) answer
  		{ bytecode pc, nil, send selector }
  	If the target is a closed PIC (polymorphic send) answer
  		{ bytecode pc, first class, target method, second class, second target method, ... }"
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #sendMcpc type: #'char *'>
  	| tuple class |
  	tuple := objectMemory
  					eeInstantiateClassIndex: ClassArrayCompactIndex
  					format: objectMemory arrayFormat
+ 					numSlots: (cogMethod isCMClosedPIC
- 					numSlots: (cogMethod cmType = CMClosedPIC
  								ifTrue: [2 * cogMethod cPICNumCases + 1]
  								ifFalse: [3]).
  	tuple = 0 ifTrue:
  		[^0].
  	objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[class := methodClassOrNil ifNil:
  					[objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
  		 objectMemory
  			storePointer: 1 ofObject: tuple withValue: class;
  			storePointer: 2 ofObject: tuple withValue: cogMethod methodObject.
  		^tuple].
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[self populate: tuple withPICInfoFor: cogMethod firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
  		^tuple].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[objectMemory
  			storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
  			storePointer: 2 ofObject: tuple withValue: cogMethod selector.
  		^tuple].
  	self error: 'invalid method type'.
  	^0 "to get Slang to type this method as answering sqInt"!

Item was changed:
  ----- Method: SistaCogit>>populate:withPICInfoFor:firstCacheTag: (in category 'method introspection') -----
  populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag
  	"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
  	 The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc cacheTag classOop entryPoint targetMethod value |
  	<var: #targetMethod type: #'CogMethod *'>
  
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		cacheTag := i = 1
  						ifTrue: [firstCacheTag]
  						ifFalse: [backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize].
  		classOop := objectRepresentation classForInlineCacheTag: cacheTag.
  		objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
  		entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
  		(cPIC containsAddress: entryPoint)
  			ifTrue:
  				[value := objectMemory splObj: SelectorDoesNotUnderstand]
  			ifFalse:
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				 self assert: targetMethod isCMMethodEtAl.
- 				 self assert: targetMethod cmType = CMMethod.
  				 value := targetMethod methodObject].
  		objectMemory storePointer: i * 2 ofObject: tuple withValue: value]!

Item was changed:
  ----- Method: SistaCogit>>printPICDataForMethods (in category 'tests') -----
  printPICDataForMethods
  	<doNotGenerate>
  	methodZone methodsDo:
  		[:cogMethod|
+ 		cogMethod isCMMethodEtAl ifTrue:
- 		cogMethod cmType = CMMethod ifTrue:
  			[(coInterpreter picDataFor: cogMethod) ifNotNil:
  				[:thePicData|
  				coInterpreter printOop: thePicData]]]!

Item was changed:
  ----- Method: SistaCogitClone>>disassembleMethod:on: (in category 'disassembly') -----
  disassembleMethod: surrogateOrAddress on: aStream
  	<doNotGenerate>
  	| cogMethod |
  	cogMethod := super disassembleMethod: surrogateOrAddress on: aStream.
+ 	(cogMethod isCMMethodEtAl
- 	(cogMethod cmType = CMMethod
  	 and: [cogMethod counters ~= 0]) ifTrue:
  		[aStream nextPutAll: 'counters:'; cr.
  		 0 to: (objectRepresentation numCountersFor: cogMethod counters) - 1 do:
  			[:i| | addr |
  			 addr := i * CounterBytes + counters.
  			 addr printOn: aStream base: 16.
  			 aStream nextPut: $:; space.
  			 (objectMemory long32At: addr) printOn: aStream base: 16.
  			 aStream cr].
  		 aStream flush]!

Item was changed:
  ----- Method: SistaCogitClone>>picDataForSendTo:methodClassIfSuper:at:bcpc: (in category 'method introspection') -----
  picDataForSendTo: cogMethod methodClassIfSuper: methodClassOrNil at: sendMcpc bcpc: sendBcpc
  	"Answer a tuple with the send data for a linked send to cogMethod.
  	 If the target is a CogMethod (monomorphic send) answer
  		{ bytecode pc, inline cache class, target method }
  	 If the target is an open PIC (megamorphic send) answer
  		{ bytecode pc, nil, send selector }
  	If the target is a closed PIC (polymorphic send) answer
  		{ bytecode pc, first class, target method, second class, second target method, ... }"
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #sendMcpc type: #'char *'>
  	| tuple class |
  	tuple := objectMemory
  					eeInstantiateClassIndex: ClassArrayCompactIndex
  					format: objectMemory arrayFormat
+ 					numSlots: (cogMethod isCMClosedPIC
- 					numSlots: (cogMethod cmType = CMClosedPIC
  								ifTrue: [2 * cogMethod cPICNumCases + 1]
  								ifFalse: [3]).
  	tuple = 0 ifTrue:
  		[^0].
  	objectMemory storePointerUnchecked: 0 ofObject: tuple withValue: (objectMemory integerObjectOf: sendBcpc).
+ 	cogMethod isCMMethodEtAl ifTrue:
- 	cogMethod cmType = CMMethod ifTrue:
  		[class := methodClassOrNil ifNil:
  					[objectRepresentation classForInlineCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger)].
  		 objectMemory
  			storePointer: 1 ofObject: tuple withValue: class;
  			storePointer: 2 ofObject: tuple withValue: cogMethod methodObject.
  		^tuple].
+ 	cogMethod isCMClosedPIC ifTrue:
- 	cogMethod cmType = CMClosedPIC ifTrue:
  		[self populate: tuple withPICInfoFor: cogMethod firstCacheTag: (backEnd inlineCacheTagAt: sendMcpc asUnsignedInteger).
  		^tuple].
+ 	cogMethod isCMOpenPIC ifTrue:
- 	cogMethod cmType = CMOpenPIC ifTrue:
  		[objectMemory
  			storePointerUnchecked: 1 ofObject: tuple withValue: objectMemory nilObject;
  			storePointer: 2 ofObject: tuple withValue: cogMethod selector.
  		^tuple].
  	self error: 'invalid method type'.
  	^0 "to get Slang to type this method as answering sqInt"!

Item was changed:
  ----- Method: SistaCogitClone>>populate:withPICInfoFor:firstCacheTag: (in category 'method introspection') -----
  populate: tuple withPICInfoFor: cPIC firstCacheTag: firstCacheTag
  	"Populate tuple (which must be large enough) with the ClosedPIC's target method class pairs.
  	 The first entry in tuple contains the bytecode pc for the send, so skip the tuple's first field."
  	<var: #cPIC type: #'CogMethod *'>
  	| pc cacheTag classOop entryPoint targetMethod value |
  	<var: #targetMethod type: #'CogMethod *'>
  
  	1 to: cPIC cPICNumCases do:
  		[:i|
  		pc := self addressOfEndOfCase: i inCPIC: cPIC.
  		cacheTag := i = 1
  						ifTrue: [firstCacheTag]
  						ifFalse: [backEnd literalBeforeFollowingAddress: pc - backEnd jumpLongConditionalByteSize].
  		classOop := objectRepresentation classForInlineCacheTag: cacheTag.
  		objectMemory storePointer: i * 2 - 1 ofObject: tuple withValue: classOop.
  		entryPoint := i = 1
  						ifTrue: [backEnd jumpLongTargetBeforeFollowingAddress: pc]
  						ifFalse: [backEnd jumpLongConditionalTargetBeforeFollowingAddress: pc].
  		"Find target from jump.  A jump to the MNU entry-point should collect #doesNotUnderstand:"
  		(cPIC containsAddress: entryPoint)
  			ifTrue:
  				[value := objectMemory splObj: SelectorDoesNotUnderstand]
  			ifFalse:
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 				 self assert: targetMethod isCMMethodEtAl.
- 				 self assert: targetMethod cmType = CMMethod.
  				 value := targetMethod methodObject].
  		objectMemory storePointer: i * 2 ofObject: tuple withValue: value]!

Item was changed:
  ----- Method: SistaCogitClone>>printPICDataForMethods (in category 'tests') -----
  printPICDataForMethods
  	<doNotGenerate>
  	methodZone methodsDo:
  		[:cogMethod|
+ 		cogMethod isCMMethodEtAl ifTrue:
- 		cogMethod cmType = CMMethod ifTrue:
  			[(coInterpreter picDataFor: cogMethod) ifNotNil:
  				[:thePicData|
  				coInterpreter printOop: thePicData]]]!



More information about the Vm-dev mailing list