[Vm-dev] [commit] r2299 - OSCogVM source as per VMMaker-oscog.27.

commits at squeakvm.org commits at squeakvm.org
Sun Sep 12 16:49:10 UTC 2010


Author: eliot
Date: 2010-09-12 09:49:10 -0700 (Sun, 12 Sep 2010)
New Revision: 2299

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/platforms/Cross/vm/sqVirtualMachine.c
   branches/Cog/src/vm/cointerp.c
   branches/Cog/src/vm/cointerp.h
   branches/Cog/src/vm/gcc3x-cointerp.c
   branches/Cog/src/vm/interp.h
   branches/Cog/stacksrc/vm/gcc3x-interp.c
   branches/Cog/stacksrc/vm/interp.c
   branches/Cog/stacksrc/vm/interp.h
Log:
OSCogVM source as per VMMaker-oscog.27.
Fix bad bug in CompiledMethod>>flushCache/primitiveFlushCacheByMethod.
Original code failed to flush the primitive embedded in the machine code
method, causing it to run the previous primitive.
Fix bad bug in the Cogit's primitiveDoPrimitiveWithArgs.  Because of the
way the process primitives "return" (they don't, they longjmp) the
popRemappableOop wasn't always executed, causing the remamp buffer
to overflow.
With these two fixes things like the following now work:
	thisContext runSimulated:
		[(1 to: 10)
			do:[:aClass| (Delay forMilliseconds: 100) wait]
			displayingProgress: 'Processing...']

Nuke the unused checking primitive stack interface (shouldPopArgs et al).


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes	2010-09-12 16:49:10 UTC (rev 2299)
@@ -128537,4 +128537,984 @@
 ----STARTUP----{28 August 2010 . 4:07:08 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
 
 
-----QUIT/NOSAVE----{28 August 2010 . 4:07:49 pm} VMMaker-Squeak4.1.image priorSource: 5189951!
\ No newline at end of file
+----QUIT/NOSAVE----{28 August 2010 . 4:07:49 pm} VMMaker-Squeak4.1.image priorSource: 5189951!
+
+----STARTUP----{5 September 2010 . 12:44:56 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!LargeIntegersPlugin methodsFor: 'oop functions' stamp: 'nice 8/29/2010 19:17'!
+digitMontgomery: firstInteger times: secondInteger modulo: thirdInteger mInvModB: mInv
+
+	| firstLen secondLen thirdLen prod |
+	<var: #over type: 'unsigned char  '>
+	firstLen := self byteSizeOfBytes: firstInteger.
+	secondLen := self byteSizeOfBytes: secondInteger.
+	thirdLen := self byteSizeOfBytes: thirdInteger.
+
+	firstLen <= thirdLen ifFalse: [^self error: 'firstInteger must be less than thirdInteger'].
+	secondLen <= thirdLen ifFalse: [^self error: 'secondInteger must be less than thirdInteger'].
+	(mInv >= 0 and: [mInv <= 255]) ifFalse: [^self error: 'mInvMod256 must be between 0 and 255'].
+	self remapOop: #(firstInteger secondInteger thirdInteger) in: [prod := interpreterProxy instantiateClass: interpreterProxy classLargePositiveInteger indexableSize: thirdLen].
+	self
+				cdigitMontgomery: (interpreterProxy firstIndexableField: firstInteger)
+				len: firstLen
+				times: (interpreterProxy firstIndexableField: secondInteger)
+				len: secondLen
+				modulo: (interpreterProxy firstIndexableField: thirdInteger)
+				len: thirdLen
+				mInvModB: mInv
+				into: (interpreterProxy firstIndexableField: prod).
+	^self normalizePositive: prod! !
+!LargeIntegersPlugin methodsFor: 'C core' stamp: 'nice 8/29/2010 19:17'!
+cdigitMontgomery: pBytesFirst
+				len: firstLen
+				times: pBytesSecond
+				len: secondLen
+				modulo: pBytesThird
+				len: thirdLen
+				mInvModB: mInv
+				into: pBytesRes
+				
+	| u limit1 limit2 limit3 accum |
+	<var: #pBytesFirst type: 'unsigned char * '>
+	<var: #pBytesSecond type: 'unsigned char * '>
+	<var: #pBytesThird type: 'unsigned char * '>
+	<var: #pBytesRes type: 'unsigned char * '>
+	limit1 := firstLen - 1.
+	limit2 := secondLen - 1.
+	limit3 := thirdLen - 1.
+	0 to: limit1 do: 
+		[:i | 
+		accum := (pBytesRes at: 0) + ((pBytesFirst at: i)*(pBytesSecond at: 0)).
+		u := accum * mInv bitAnd: 255.
+		accum :=  accum + (u * (pBytesThird at: 0)).
+		1 to: limit2 do: [:k |
+			accum := (accum >> 8) + (pBytesRes at: k) + ((pBytesFirst at: i)*(pBytesSecond at: k)) + (u * (pBytesThird at: k)).
+			pBytesRes at: k-1 put: (accum bitAnd: 255)].
+		secondLen to: limit3 do: [:k |
+			accum := (accum >> 8) + (pBytesRes at: k) + (u * (pBytesThird at: k)).
+			pBytesRes at: k-1 put: (accum bitAnd: 255)].
+		accum := accum >> 8.
+		pBytesRes at: limit3 put: (accum bitAnd: 255)].
+	firstLen to: limit3 do: 
+		[:i | 
+		accum := (pBytesRes at: 0).
+		u := accum * mInv bitAnd: 255.
+		accum := accum + (u * (pBytesThird at: 0)).
+		1 to: limit3 do: [:k |
+			accum := (accum >> 8) + (pBytesRes at: k) + (u * (pBytesThird at: k)).
+			pBytesRes at: k-1 put: (accum bitAnd: 255)].
+		accum := accum >> 8.
+		pBytesRes at: limit3 put: (accum bitAnd: 255)].
+	(self cDigitCompare: pBytesThird with: pBytesRes len: thirdLen) = 1 ifFalse: [
+		self cDigitSub: pBytesThird len: thirdLen with: pBytesRes len: thirdLen into: pBytesRes].! !
+!LargeIntegersPlugin methodsFor: 'Integer primitives' stamp: 'nice 7/12/2008 03:43'!
+primMontgomeryTimes: secondOperandInteger modulo: thirdModuloInteger mInvModB: smallInverseInteger
+	| firstLarge secondLarge firstInteger thirdLarge |
+	self debugCode: [self msg: 'montgomeryTimes: secondOperandInteger modulo: thirdModuloInteger mInvModB: smallInverseInteger'].
+	firstInteger := self
+				primitive: 'primMontgomeryTimesModulo'
+				parameters: #(Integer Integer SmallInteger )
+				receiver: #Integer.
+	(interpreterProxy isIntegerObject: firstInteger)
+		ifTrue: ["convert it to a not normalized LargeInteger"
+			self remapOop: #(secondOperandInteger thirdModuloInteger) in: [firstLarge := self createLargeFromSmallInteger: firstInteger]]
+		ifFalse: [firstLarge := firstInteger].
+	(interpreterProxy isIntegerObject: secondOperandInteger)
+		ifTrue: ["convert it to a not normalized LargeInteger"
+			self remapOop: #(firstLarge thirdModuloInteger) in: [secondLarge := self createLargeFromSmallInteger: secondOperandInteger]]
+		ifFalse: [secondLarge := secondOperandInteger].
+	(interpreterProxy isIntegerObject: thirdModuloInteger)
+		ifTrue: ["convert it to a not normalized LargeInteger"
+			self remapOop: #(firstLarge secondLarge) in: [thirdLarge := self createLargeFromSmallInteger: thirdModuloInteger]]
+		ifFalse: [thirdLarge := thirdModuloInteger].
+	^ self digitMontgomery: firstLarge times: secondLarge modulo: thirdLarge mInvModB: smallInverseInteger! !
+
+----QUIT----{5 September 2010 . 12:48:39 pm} VMMaker-Squeak4.1.image priorSource: 5189951!
+
+----STARTUP----{5 September 2010 . 12:53:35 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+SystemNavigation new browseAllCallsOn: #pushRemappableOop: localTo: LargeIntegersPlugin!
+
+SystemNavigation new browseAllCallsOn: #pushRemappableOop: localTo: LargeIntegersPlugin!
+
+SystemNavigation new browseAllCallsOn: #instantiateClass:indexableSize: localTo: LargeIntegersPlugin!
+
+1+2!
+
+----STARTUP----{11 September 2010 . 1:01:13 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!StackInterpreter methodsFor: 'control primitives' stamp: 'eem 9/11/2010 13:00' prior: 37528669!
+primitiveDoPrimitiveWithArgs
+	| argumentArray arraySize index primIdx |
+	argumentArray := self stackTop.
+	(self isArray: argumentArray) ifFalse: [^self primitiveFail].
+	arraySize := self fetchWordLengthOf: argumentArray.
+	self success: (self roomToPushNArgs: arraySize).
+
+	primIdx := self stackIntegerValue: 1.
+	self successful ifFalse: [^self primitiveFail]. "invalid args"
+
+	"Pop primIndex and argArray, then push args in place..."
+	self pop: 2.
+	primitiveFunctionPointer := self functionPointerFor: primIdx inClass: nil.
+	argumentCount := arraySize.
+	index := 1.
+	[index <= argumentCount] whileTrue:
+		[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
+		 index := index + 1].
+
+	self isPrimitiveFunctionPointerAnIndex ifTrue:
+		[primitiveFunctionPointer = 0 ifTrue:
+			[^self primitiveFail].
+		self externalQuickPrimitiveResponse.
+		^nil].
+	"Run the primitive (sets primFailCode)"
+	self pushRemappableOop: argumentArray. "prim might alloc/gc"
+	lkupClass := nilObj.
+	self slowPrimitiveResponse.
+	argumentArray := self popRemappableOop.
+	self successful ifFalse: "If primitive failed, then restore state for failure code"
+		[self pop: arraySize.
+		 self pushInteger: primIdx.
+		 self push: argumentArray.
+		 argumentCount := 2]! !
+
+LargeIntegersPlugin removeSelector: #cdigitMontgomery:len:times:len:modulo:len:mInvModB:into:!
+
+LargeIntegersPlugin removeSelector: #digitMontgomery:times:modulo:mInvModB:!
+
+LargeIntegersPlugin removeSelector: #primMontgomeryTimes:modulo:mInvModB:!
+
+----QUIT----{11 September 2010 . 1:37:01 pm} VMMaker-Squeak4.1.image priorSource: 5194997!
+
+----STARTUP----{11 September 2010 . 3:14:58 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+VMClass subclass: #ObjectMemory
+	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcSemaphoreIndex gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount statPendingFinalizationSignals forceTenureFlag gcStartUsecs'
+	classVariableNames: 'AllButHashBits AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit Byte0Mask Byte0Shift Byte1Mask Byte1Shift Byte1ShiftNegated Byte2Mask Byte2Shift Byte3Mask Byte3Shift Byte3ShiftNegated Byte4Mask Byte4Shift Byte4ShiftNegated Byte5Mask Byte5Shift Byte5ShiftNegated Byte6Mask Byte6Shift Byte7Mask Byte7Shift Byte7ShiftNegated Bytes3to0Mask Bytes7to4Mask CharacterTable ClassAlien ClassArray ClassArrayCompactIndex ClassBitmap ClassBlockClosure ClassBlockClosureCompactIndex ClassBlockContext ClassBlockContextCompactIndex ClassByteArray ClassByteStringCompactIndex ClassCharacter ClassCompiledMethod ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFloatCompactIndex ClassInteger ClassLargeNegativeInteger ClassLargeNegativeIntegerCompactIndex ClassLargePositiveInteger  ForeignCallbackProcess SelectorAttemptToAssign ClassLargePositiveIntegerCompactIndex ClassMessage ClassMethodContext ClassMethodContextCompactIndex ClassMutex ClassPoint ClassProcess ClassSemaphore ClassString ClassUnsafeAlien CompactClassMask CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ContextFixedSizePlusHeader CtxtTempFrameStart DoBalanceChecks Done ExternalObjectsArray ExtraRootSize FalseObject GCTopMarker HashBits HeaderTypeClass HeaderTypeExtraBytes HeaderTypeFree HeaderTypeGC InvokeCallbackSelector LargeContextBit LargeContextSize NilContext NilObject PrimErrTableIndex PrimNoErr ProcessInExternalCodeTag ProcessSignalingLowSpace RemapBufferSize RootTableRedZone RootTableSize SchedulerAssociation SelectorAboutToReturn SelectorCannotInterpret SelectorCannotReturn SelectorDoesNotUnderstand SelectorMustBeBoolean SelectorRunWithIn SmallContextSize SpecialSelectors StartField StartObj TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject Upward VMBIGENDIAN WeakRootTableSize WordMask'
+	poolDictionaries: 'VMBasicConstants VMObjectOffsets VMSqueakV3ObjectRepresentationConstants'
+	category: 'VMMaker-Interpreter'!
+
+VMClass subclass: #ObjectMemory
+	instanceVariableNames: 'memory youngStart endOfMemory memoryLimit nilObj falseObj trueObj specialObjectsOop rootTable rootTableCount extraRoots extraRootCount weakRoots weakRootCount child field parentField freeBlock lastHash allocationCount lowSpaceThreshold signalLowSpace compStart compEnd fwdTableNext fwdTableLast remapBuffer remapBufferCount allocationsBetweenGCs tenuringThreshold gcSemaphoreIndex gcBiasToGrow gcBiasToGrowGCLimit gcBiasToGrowThreshold statFullGCs statIncrGCs statFullGCUsecs statIncrGCUsecs statGCEndTime statIGCDeltaUsecs statTenures statRootTableOverflows freeContexts freeLargeContexts interruptCheckCounter totalObjectCount shrinkThreshold growHeadroom headerTypeBytes youngStartLocal statMarkCount statMarkCountLocal statSweepCount statMkFwdCount statCompMoveCount statGrowMemory statShrinkMemory statRootTableCount statAllocationCount statSurvivorCount statSpecialMarkCount statPendingFinalizationSignals forceTenureFlag gcStartUsecs'
+	classVariableNames: 'AllButHashBits AllButMarkBit AllButMarkBitAndTypeMask AllButRootBit Byte0Mask Byte0Shift Byte1Mask Byte1Shift Byte1ShiftNegated Byte2Mask Byte2Shift Byte3Mask Byte3Shift Byte3ShiftNegated Byte4Mask Byte4Shift Byte4ShiftNegated Byte5Mask Byte5Shift Byte5ShiftNegated Byte6Mask Byte6Shift Byte7Mask Byte7Shift Byte7ShiftNegated Bytes3to0Mask Bytes7to4Mask CharacterTable ClassAlien ClassArray ClassArrayCompactIndex ClassBitmap ClassBlockClosure ClassBlockClosureCompactIndex ClassBlockContext ClassWeakFinalizer ClassBlockContextCompactIndex ClassByteArray ClassByteStringCompactIndex ClassCharacter ClassCompiledMethod ClassExternalAddress ClassExternalData ClassExternalFunction ClassExternalLibrary ClassExternalStructure ClassFloat ClassFloatCompactIndex ClassInteger ClassLargeNegativeInteger ClassLargeNegativeIntegerCompactIndex ClassLargePositiveInteger ClassLargePositiveIntegerCompactIndex ClassMessage ClassMethodContext ClassMethodContextCompactIndex ClassMutex ClassPoint ClassProcess ClassSemaphore ClassString ClassUnsafeAlien CompactClassMask CompactClasses ConstMinusOne ConstOne ConstTwo ConstZero ContextFixedSizePlusHeader CtxtTempFrameStart DoBalanceChecks Done ExternalObjectsArray ExtraRootSize FalseObject ForeignCallbackProcess GCTopMarker HashBits HeaderTypeClass HeaderTypeExtraBytes HeaderTypeFree HeaderTypeGC InvokeCallbackSelector LargeContextBit LargeContextSize NilContext NilObject PrimErrTableIndex PrimNoErr ProcessInExternalCodeTag ProcessSignalingLowSpace RemapBufferSize RootTableRedZone RootTableSize SchedulerAssociation SelectorAboutToReturn SelectorAttemptToAssign SelectorCannotInterpret SelectorCannotReturn SelectorDoesNotUnderstand SelectorMustBeBoolean SelectorRunWithIn SmallContextSize SpecialSelectors StartField StartObj TheDisplay TheFinalizationSemaphore TheInputSemaphore TheInterruptSemaphore TheLowSpaceSemaphore TheTimerSemaphore TrueObject Upward VMBIGENDIAN WeakRootTableSize WordMask'
+	poolDictionaries: 'VMBasicConstants VMObjectOffsets VMSqueakV3ObjectRepresentationConstants'
+	category: 'VMMaker-Interpreter'!
+!StackInterpreter methodsFor: 'system control primitives' stamp: 'eem 9/11/2010 15:10' prior: 37958303!
+primitiveFlushCacheByMethod
+	"The receiver is a compiledMethod.  Clear all entries in the method lookup cache that refer to this method, presumably because it has been redefined, overridden or removed."
+	| probe oldMethod primIdx |
+	oldMethod := self stackTop.
+	probe := 0.
+	1 to: MethodCacheEntries do:
+		[:i |
+		(methodCache at: probe + MethodCacheMethod) = oldMethod ifTrue:
+			[methodCache at: probe + MethodCacheSelector put: 0].
+		probe := probe + MethodCacheEntrySize].
+	primIdx := self primitiveIndexOf: oldMethod.
+	primIdx = PrimitiveExternalCallIndex ifTrue:
+		["It's primitiveExternalCall"
+		self flushExternalPrimitiveOf: oldMethod]! !
+!CoInterpreter methodsFor: 'system control primitives' stamp: 'eem 9/11/2010 15:10' prior: 34628472!
+primitiveFlushCacheByMethod
+	"The receiver is a compiledMethod.  Clear all entries in the method lookup cache that
+	 refer to this method, presumably because it has been redefined, overridden or removed.
+	 Override to flush appropriate machine code caches also."
+	| probe oldMethod primIdx |
+	oldMethod := self stackTop.
+	probe := 0.
+	1 to: MethodCacheEntries do:
+		[:i |
+		(methodCache at: probe + MethodCacheMethod) = oldMethod ifTrue:
+			[methodCache at: probe + MethodCacheSelector put: 0].
+		probe := probe + MethodCacheEntrySize].
+	primIdx := self primitiveIndexOf: oldMethod.
+	primIdx = PrimitiveExternalCallIndex ifTrue:
+		["It's primitiveExternalCall"
+		self flushExternalPrimitiveOf: oldMethod].
+	(self methodHasCogMethod: oldMethod) ifTrue:
+		[cogit unlinkSendsTo: (self cogMethodOf: oldMethod)]! !
+!CogVMSimulator methodsFor: 'primitive support' stamp: 'eem 9/11/2010 12:57' prior: 35048473!
+isPrimitiveFunctionPointerAnIndex
+	"We save slots in the method cache by using the primitiveFunctionPointer
+	 to hold either a function pointer or the index of a quick primitive. Since
+	 quick primitive indices are small they can't be confused with function
+	 addresses.  But since we use 1001 and up for external primitives that
+	 would be functions in the C VM but are indices under simulation we treat
+	 values above 1000 as if they were pointers (actually indices into the
+	 externalPrimitiveTable)"
+
+	^primitiveFunctionPointer isInteger
+	  and: [primitiveFunctionPointer >= 0
+	  and: [primitiveFunctionPointer <= MaxQuickPrimitiveIndex]]! !
+!ObjectMemory class methodsFor: 'initialization' stamp: 'eem 9/10/2010 15:58' prior: 36900799!
+initializeSpecialObjectIndices
+	"Initialize indices into specialObjects array."
+
+	NilObject := 0.
+	FalseObject := 1.
+	TrueObject := 2.
+	SchedulerAssociation := 3.
+	ClassBitmap := 4.
+	ClassInteger := 5.
+	ClassString := 6. "N.B.  Actually class ByteString"
+	ClassArray := 7.
+	"SmalltalkDictionary := 8."  "Do not delete!!"
+	ClassFloat := 9.
+	ClassMethodContext := 10.
+	ClassBlockContext := 11.
+	ClassPoint := 12.
+	ClassLargePositiveInteger := 13.
+	TheDisplay := 14.
+	ClassMessage := 15.
+	ClassCompiledMethod := 16.
+	TheLowSpaceSemaphore := 17.
+	ClassSemaphore := 18.
+	ClassCharacter := 19.
+	SelectorDoesNotUnderstand := 20.
+	SelectorCannotReturn := 21.
+	ProcessSignalingLowSpace := 22.	"was TheInputSemaphore"
+	SpecialSelectors := 23.
+	CharacterTable := 24.
+	SelectorMustBeBoolean := 25.
+	ClassByteArray := 26.
+	ClassProcess := 27.
+	CompactClasses := 28.
+	TheTimerSemaphore := 29.
+	TheInterruptSemaphore := 30.
+	SelectorCannotInterpret := 34.
+	"Was MethodContextProto := 35."
+	ClassBlockClosure := 36.
+	"Was BlockContextProto := 37."
+	ExternalObjectsArray := 38.
+	ClassMutex := 39.
+	"Was: ClassTranslatedMethod := 40."
+	ProcessInExternalCodeTag := 40.
+	TheFinalizationSemaphore := 41.
+	ClassLargeNegativeInteger := 42.
+
+	ClassExternalAddress := 43.
+	ClassExternalStructure := 44.
+	ClassExternalData := 45.
+	ClassExternalFunction := 46.
+	ClassExternalLibrary := 47.
+
+	SelectorAboutToReturn := 48.
+	SelectorRunWithIn := 49.
+
+	SelectorAttemptToAssign := 50.
+	"PrimErrTableIndex := 51. in Interpreter class>>initializePrimitiveErrorCodes"
+	ClassAlien := 52.
+	InvokeCallbackSelector := 53.
+	ClassUnsafeAlien := 54.
+
+	ClassWeakFinalizer := 55.
+
+	ForeignCallbackProcess := 56! !
+
+----QUIT----{11 September 2010 . 3:19 pm} VMMaker-Squeak4.1.image priorSource: 5197222!
+
+----STARTUP----{11 September 2010 . 3:19:13 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{11 September 2010 . 3:19:22 pm} VMMaker-Squeak4.1.image priorSource: 5207778!
+
+----STARTUP----{11 September 2010 . 3:23:03 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!ObjectMemory methodsFor: 'interpreter access' stamp: 'anon 9/11/2010 15:24' prior: 36883594!
+pushRemappableOop: oop
+	"Record the given object in a the remap buffer. Objects in this buffer are remapped when a compaction occurs. This facility is used by the interpreter to ensure that objects in temporary variables are properly remapped."
+	<api>
+	self assert: (self addressCouldBeOop: oop).
+	remapBuffer at: (remapBufferCount := remapBufferCount + 1) put: oop.! !
+
+----QUIT----{11 September 2010 . 3:24:37 pm} VMMaker-Squeak4.1.image priorSource: 5207778!
+
+----STARTUP----{11 September 2010 . 3:40:30 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!CoInterpreter methodsFor: 'primitive support' stamp: 'eem 9/11/2010 15:39' prior: 34604392!
+slowPrimitiveResponse
+	"Called under the assumption that primFunctionPtr has been preloaded"
+	| nArgs savedFramePointer savedStackPointer remapCount |
+	<inline: true>
+	<asmLabel: false>
+	<var: #savedFramePointer type: #'char *'>
+	<var: #savedStackPointer type: #'char *'>
+	cogit recordPrimTrace ifTrue:
+		[self fastLogPrim: messageSelector].
+	FailImbalancedPrimitives ifTrue:
+		[nArgs := argumentCount.
+		 savedStackPointer := stackPointer.
+		 savedFramePointer := framePointer].
+	remapCount := self remapBufferCount.
+	self initPrimCall.
+	self dispatchFunctionPointer: primitiveFunctionPointer.
+	self assert: remapCount == self remapBufferCount.
+	FailImbalancedPrimitives ifTrue:
+		[(self successful
+		  and: [framePointer = savedFramePointer
+		  and: [(self isMachineCodeFrame: framePointer) not]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
+			[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
+				"Soon make this a message send of e.g. unbalancedPrimitive to the current process or context"
+				[stackPointer := savedStackPointer. "This is necessary but insufficient; the result may still have been written to the stack."
+				 self failUnbalancedPrimitive]]].
+	"If we are profiling, take accurate primitive measures"
+	nextProfileTick > 0 ifTrue:
+		[self checkProfileTick: newMethod].
+	^self successful! !
+!StackInterpreter methodsFor: 'primitive support' stamp: 'eem 9/11/2010 15:39' prior: 37862961!
+slowPrimitiveResponse
+	"Called under the assumption that primFunctionPtr has been preloaded"
+	| delta nArgs savedFramePointer savedNewMethod savedStackPointer expectedPops remapCount |
+	<inline: true>
+	<asmLabel: false>
+	<var: #savedFramePointer type: #'char *'>
+	<var: #savedStackPointer type: #'char *'>
+	FailImbalancedPrimitives
+		ifTrue:
+			[nArgs := argumentCount.
+			 savedStackPointer := stackPointer.
+			 savedFramePointer := framePointer]
+		ifFalse:
+			[DoBalanceChecks ifTrue:"check stack balance"
+				[nArgs := argumentCount.
+				 delta := framePointer - stackPointer.
+				 "If frame pointer changes then primitive has sent or unwound.
+				  Stack will appear unbalanced in this case."
+				 savedFramePointer := framePointer.
+				 savedNewMethod := newMethod]].
+	remapCount := self remapBufferCount.
+	self initPrimCall.
+	self dispatchFunctionPointer: primitiveFunctionPointer.
+	self assert: remapCount == self remapBufferCount.
+	shouldPopArgs ifTrue:[
+		"This was a plugin primitive. If the primitive was successful, pop the args,
+		push the return value. Otherwise leave things alone."
+		self successful ifTrue:[
+			expectedPops := argumentCount.
+			self pop: expectedPops.
+			primResult = 0 ifFalse:[self pop: 1 thenPush: primResult].
+		] ifFalse:[expectedPops := 0].
+		primResult := 0. "clear result"
+		"Verify that the primitive popped the expected number of args.
+		If we have zero primPops assume access via methodArg: etc. 
+		and don't complain."
+		(primPops = 0 or:[expectedPops = primPops]) ifFalse:[
+			self cCode: 'fprintf(stderr,"[VM]: Warning: Primitive popped wrong number of args\n")'.
+			self printCallStack.
+		].
+	].
+	FailImbalancedPrimitives
+		ifTrue:
+			[(self successful
+			  and: [framePointer = savedFramePointer
+			  and: [(self isMachineCodeFrame: framePointer) not]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
+				[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
+					"Soon make this a message send of e.g. unbalancedPrimitive to the current process or context"
+					[stackPointer := savedStackPointer. "This is necessary but insufficient; the result may still have been written to the stack."
+					 self failUnbalancedPrimitive]]]
+		ifFalse:
+			[(DoBalanceChecks
+			 and: [framePointer = savedFramePointer]) ifTrue:
+				[(self balancedStack: delta withArgs: nArgs) ifFalse:
+					[self printUnbalancedStack: (self primitiveIndexOf: savedNewMethod)]]].
+	"If we are profiling, take accurate primitive measures"
+	nextProfileTick > 0 ifTrue:
+		[self checkProfileTick: newMethod].
+	^self successful! !
+
+----QUIT----{11 September 2010 . 3:44 pm} VMMaker-Squeak4.1.image priorSource: 5208678!
+
+----STARTUP----{11 September 2010 . 3:45:57 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 11 September 2010 at 3:51:01 pm'!
+!ObjectMemory methodsFor: 'accessing' stamp: 'eem 9/11/2010 15:50'!
+remapBufferCount
+	<cmacro: '() GIV(remapBufferCount)'>
+	^remapBufferCount! !
+
+----End fileIn of /Users/eliot/Cog/ObjectMemory-remapBufferCount.st----!
+
+----SNAPSHOT----{11 September 2010 . 3:53:03 pm} VMMaker-Squeak4.1.image priorSource: 5213030!
+
+----QUIT/NOSAVE----{11 September 2010 . 3:53:32 pm} VMMaker-Squeak4.1.image priorSource: 5213556!
+
+----STARTUP----{11 September 2010 . 4:09:39 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 11 September 2010 at 4:08:42 pm'!
+!StackInterpreter methodsFor: 'control primitives' stamp: 'eem 9/11/2010 16:07' prior: 38750156!
+primitiveDoPrimitiveWithArgs
+	| argumentArray arraySize index primIdx |
+	argumentArray := self stackTop.
+	(self isArray: argumentArray) ifFalse: [^self primitiveFail].
+	arraySize := self fetchWordLengthOf: argumentArray.
+	self success: (self roomToPushNArgs: arraySize).
+
+	primIdx := self stackIntegerValue: 1.
+	self successful ifFalse: [^self primitiveFail]. "invalid args"
+
+	primitiveFunctionPointer := self functionPointerFor: primIdx inClass: nil.
+	primitiveFunctionPointer = 0 ifTrue:
+		[^self primitiveFail].
+
+	"Pop primIndex and argArray, then push args in place..."
+	self pop: 2.
+	argumentCount := arraySize.
+	index := 1.
+	[index <= argumentCount] whileTrue:
+		[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
+		 index := index + 1].
+
+	self isPrimitiveFunctionPointerAnIndex ifTrue:
+		[self externalQuickPrimitiveResponse.
+		^nil].
+	"Run the primitive (sets primFailCode)"
+	self pushRemappableOop: argumentArray. "prim might alloc/gc"
+	lkupClass := nilObj.
+	self slowPrimitiveResponse.
+	argumentArray := self popRemappableOop.
+	self successful ifFalse: "If primitive failed, then restore state for failure code"
+		[self pop: arraySize.
+		 self pushInteger: primIdx.
+		 self push: argumentArray.
+		 argumentCount := 2]! !
+
+----End fileIn of /Users/eliot/Cog/StackInterpreter-primitiveDoPrimitiveWithArgs.st----!
+
+----QUIT----{11 September 2010 . 4:10:43 pm} VMMaker-Squeak4.1.image priorSource: 5213556!
+
+----STARTUP----{12 September 2010 . 8:14:04 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+CoInterpreter subclass: #CogVMSimulator
+	instanceVariableNames: 'enableCog byteCount sendCount printSends traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'VMMaker-JITSimulation'!
+
+(Array streamContents: [ : stream |
+		SystemNavigation default allBehaviorsDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ]!
+
+(Array streamContents: [ : stream |
+		VMClass withAllSubclassesDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ]!
+!CoInterpreter class methodsFor: 'translation' stamp: 'eem 9/12/2010 06:00' prior: 34648211!
+preGenerationHook: aCCodeGenerator
+	"Override to undo the hiding of primitiveClosureValueNoContextSwitch"
+	super preGenerationHook: aCCodeGenerator.
+	(aCCodeGenerator methodNamed: #primitiveClosureValueNoContextSwitch) static: false! !
+
+CoInterpreter removeSelector: #methodReturnValue:!
+!CoInterpreter methodsFor: 'primitive support' stamp: 'eem 9/12/2010 06:16' prior: 38763420!
+slowPrimitiveResponse
+	"Called under the assumption that primFunctionPtr has been preloaded"
+	| nArgs savedFramePointer savedStackPointer |
+	<inline: true>
+	<asmLabel: false>
+	<var: #savedFramePointer type: #'char *'>
+	<var: #savedStackPointer type: #'char *'>
+	cogit recordPrimTrace ifTrue:
+		[self fastLogPrim: messageSelector].
+	FailImbalancedPrimitives ifTrue:
+		[nArgs := argumentCount.
+		 savedStackPointer := stackPointer.
+		 savedFramePointer := framePointer].
+	self initPrimCall.
+	self dispatchFunctionPointer: primitiveFunctionPointer.
+	(FailImbalancedPrimitives
+	and: [self successful
+	and: [framePointer = savedFramePointer
+	and: [(self isMachineCodeFrame: framePointer) not]]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
+		[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
+			[self flag: 'Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context'.
+			 "This is necessary but insufficient; the result may still have been written to the stack.
+			   At least we'll know something is wrong."
+			 stackPointer := savedStackPointer.
+			 self failUnbalancedPrimitive]].
+	"If we are profiling, take accurate primitive measures"
+	nextProfileTick > 0 ifTrue:
+		[self checkProfileTick: newMethod].
+	^self successful! !
+
+ObjectMemory subclass: #Interpreter
+	instanceVariableNames: 'activeContext theHomeContext method receiver instructionPointer stackPointer localIP localSP localHomeContext localReturnContext localReturnValue messageSelector argumentCount newMethod currentBytecode successFlag primitiveIndex primitiveFunctionPointer methodCache atCache lkupClass reclaimableContextCount nextPollTick nextWakeupTick lastTick interruptKeycode interruptPending semaphoresToSignalA semaphoresUseBufferA semaphoresToSignalCountA semaphoresToSignalB semaphoresToSignalCountB  savedWindowSize fullScreenFlag deferDisplayUpdates pendingFinalizationSignals compilerInitialized  extraVMMemory  receiverClass  interpreterProxy showSurfaceFn interruptCheckCounterFeedBackReset interruptChecksEveryNms externalPrimitiveTable primitiveTable globalSessionID jmpBuf jmpDepth jmpMax suspendedCallbacks suspendedMethods profileProcess profileMethod profileSemaphore nextProfileTick metaclassSizeBytes statIOProcessEvents statCheckForEvents statQuickCheckForEvents statProcessSwitch'
+	classVariableNames: 'ActiveProcessIndex AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BlockArgumentCountIndex BlockMethodIndex BytecodeTable CacheProbeMax CallerIndex CharacterValueIndex ClosureIndex ClosureMethodIndex CompilerHooksSize CrossedX DirBadPath DirEntryFound DirNoMoreEntries EndOfRun ExcessSignalsIndex FirstLinkIndex HomeIndex InitialIPIndex JitterTable LastLinkIndex LiteralStart MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MessageArgumentsIndex MessageDictionaryIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MillisecondClockMask MyListIndex NextLinkIndex PrimitiveExternalCallIndex PrimitiveTable PriorityIndex ProcessListsIndex SelectorStart SemaphoresToSignalSize StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TempFrameStart XIndex YIndex'
+	poolDictionaries: 'VMMethodCacheConstants VMObjectOffsets'
+	category: 'VMMaker-Interpreter'!
+
+(Array streamContents: [ : stream |
+		VMClass withAllSubclassesDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ] !
+!StackInterpreter class methodsFor: 'translation' stamp: 'eem 9/12/2010 05:59' prior: 38080976!
+requiredMethodNames
+	"return the list of method names that should be retained for export or other support reasons"
+	| requiredList |
+	requiredList := self exportAPISelectors.
+	requiredList addAll: NewObjectMemory requiredMethodNames.
+	"A number of methods required by VM support code, jitter, specific platforms etc"
+	requiredList addAll: #(
+		assertValidExecutionPointe:r:s:
+		characterForAscii: checkedLongAt:
+		delayExpired
+		findClassOfMethod:forReceiver: findSelectorOfMethod:forReceiver:
+			forceInterruptCheck forceInterruptCheckFromHeartbeat fullDisplayUpdate
+		getCurrentBytecode getFullScreenFlag getInterruptKeycode getInterruptPending
+			getSavedWindowSize getThisSessionID
+		highBit:
+		interpret
+		loadInitialContext
+		objectBefore: objectExactlyBefore: oopFromChunk:
+		primitiveFail primitiveFailFor: primitiveFlushExternalPrimitives printAllStacks printCallStack printContext:
+			printExternalHeadFrame printFramesInPage: printFrame: printHeadFrame printMemory printOop:
+				printStackPages printStackPageList printStackPagesInUse printStackPageListInUse
+		readableFormat: readImageFromFile:HeapSize:StartingAt:
+		setFullScreenFlag: setInterruptKeycode: setInterruptPending: setInterruptCheckChain:
+			setSavedWindowSize: success:
+		validInstructionPointer:inMethod:framePointer:).
+
+	"Nice to actually have all the primitives available"
+	requiredList addAll: (self primitiveTable select: [:each| each isSymbol]).
+
+	"InterpreterProxy is the internal analogue of sqVirtualMachine.c, so make sure to keep all those"
+	InterpreterProxy organization categories do:
+		[:cat |
+		((cat ~= 'initialize') and: [cat ~= 'private']) ifTrue:
+			[requiredList addAll: (InterpreterProxy organization listAtCategoryNamed: cat)]].
+
+	^requiredList! !
+!StackInterpreter methodsFor: 'object memory support' stamp: 'eem 9/12/2010 06:52' prior: 37827476!
+checkInterpreterIntegrity
+	"Perform an integrity/leak check using the heapMap.  Assume
+	 clearLeakMapAndMapAccessibleObjects has set a bit at each
+	 object's header.  Check that all oops in the interpreter's state
+	 points to a header.  Answer if all checks pass."
+	| ok |
+	ok := true.
+	(self checkOopIntegrity: specialObjectsOop named: 'specialObjectsOop')ifFalse:
+		[ok := false].
+	(self isIntegerObject: messageSelector) ifFalse:
+		[(self checkOopIntegrity: messageSelector named: 'messageSelector')ifFalse:
+			[ok := false]].
+	(self checkOopIntegrity: newMethod named: 'newMethod')ifFalse:
+		[ok := false].
+	(self checkOopIntegrity: lkupClass named: 'lkupClass')ifFalse:
+		[ok := false].
+	(self checkOopIntegrity: profileProcess named: 'profileProcess')ifFalse:
+		[ok := false].
+	(self checkOopIntegrity: profileMethod named: 'profileMethod')ifFalse:
+		[ok := false].
+	(self checkOopIntegrity: profileSemaphore named: 'profileSemaphore')ifFalse:
+		[ok := false].
+	tempOop = 0 ifFalse:
+		[(self checkOopIntegrity: tempOop named: 'tempOop')ifFalse:
+			[ok := false]].
+
+	"Callback support - check suspended callback list"
+	1 to: jmpDepth do:
+		[:i|
+		(self checkOopIntegrity: (suspendedCallbacks at: i) named: 'suspendedCallbacks' index: i) ifFalse:
+			[ok := false].
+		(self checkOopIntegrity: (suspendedMethods at: i) named: 'suspendedMethods' index: i) ifFalse:
+			[ok := false]].
+
+	self checkLogIntegrity ifFalse:
+		[ok := false].
+
+	^ok! !
+!StackInterpreter methodsFor: 'primitive support' stamp: 'eem 9/12/2010 06:03' prior: 37849632!
+initPrimCall
+	"Set the failure code/success flag in preparation for calling a primitve.
+	 If primFailCode is non-zero a primitive has failed.  If primFailCode is
+	 greater than one then its value indicates the reason for failure."
+	<inline: true>
+	primFailCode := 0! !
+!StackInterpreter methodsFor: 'initialization' stamp: 'eem 9/12/2010 06:43' prior: 37821595!
+initializeInterpreter: bytesToShift 
+	"Initialize Interpreter state before starting execution of a new image."
+	interpreterProxy := self sqGetInterpreterProxy.
+	self dummyReferToProxy.
+	self initializeObjectMemory: bytesToShift.
+	self checkAssumedCompactClasses.
+	primFailCode := 0.
+	metaclassSizeBytes := self sizeBitsOf: (self fetchClassOfNonInt: (self splObj: ClassArray)).	"determine actual (Metaclass instSize * 4)"
+	stackLimit := 0. "This is also the initialization flag for the stack system."
+	stackPage := overflowedPage := 0.
+	extraFramesToMoveOnOverflow := 0.
+	self setMethod: nilObj.
+	messageSelector := nilObj.
+	newMethod := nilObj.
+	lkupClass := nilObj.
+	self flushMethodCache.
+	self flushAtCache.
+	self initialCleanup.
+	highestRunnableProcessPriority := 0.
+	nextProfileTick := 0.
+	profileSemaphore := nilObj.
+	profileProcess := nilObj.
+	profileMethod := nilObj.
+	nextPollUsecs := 0.
+	nextWakeupUsecs := 0.
+	tempOop := 0.
+	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
+	interruptPending := false.
+	deferDisplayUpdates := false.
+	pendingFinalizationSignals := statPendingFinalizationSignals := 0.
+	globalSessionID := 0.
+	[globalSessionID = 0]
+		whileTrue: [globalSessionID := self
+						cCode: 'time(NULL) + ioMSecs()'
+						inSmalltalk: [(Random new next * SmallInteger maxVal) asInteger]].
+	jmpDepth := 0.
+	jmpMax := MaxJumpBuf. "xxxx: Must match the definition of jmpBuf and suspendedCallbacks"
+	longRunningPrimitiveStartUsecs :=
+	longRunningPrimitiveStopUsecs := 0.
+	maxExtSemTabSizeSet := false.
+	statForceInterruptCheck := 0.
+	statStackOverflow := 0.
+	statCheckForEvents := 0.
+	statProcessSwitch := 0.
+	statIOProcessEvents := 0.
+	statStackPageDivorce := 0! !
+!StackInterpreter methodsFor: 'object memory support' stamp: 'eem 9/12/2010 06:48' prior: 37831752!
+mapInterpreterOops
+	"Map all oops in the interpreter's state to their new values 
+	during garbage collection or a become: operation."
+	"Assume: All traced variables contain valid oops."
+	| oop |
+	nilObj := self remap: nilObj.
+	falseObj := self remap: falseObj.
+	trueObj := self remap: trueObj.
+	specialObjectsOop := self remap: specialObjectsOop.
+	self mapStackPages.
+	self mapMachineCode.
+	self mapTraceLogs.
+	self mapVMRegisters.
+	self mapProfileState.
+	tempOop = 0 ifFalse: [tempOop := self remap: tempOop].
+	1 to: remapBufferCount do: [:i | 
+			oop := remapBuffer at: i.
+			(self isIntegerObject: oop)
+				ifFalse: [remapBuffer at: i put: (self remap: oop)]].
+
+	"Callback support - trace suspended callback list"
+	1 to: jmpDepth do:[:i|
+		oop := suspendedCallbacks at: i.
+		(self isIntegerObject: oop) 
+			ifFalse:[suspendedCallbacks at: i put: (self remap: oop)].
+		oop := suspendedMethods at: i.
+		(self isIntegerObject: oop) 
+			ifFalse:[suspendedMethods at: i put: (self remap: oop)].
+	].
+! !
+!StackInterpreter methodsFor: 'object memory support' stamp: 'eem 9/12/2010 06:49' prior: 37838165!
+markAndTraceInterpreterOops: fullGCFlag
+	"Mark and trace all oops in the interpreter's state."
+	"Assume: All traced variables contain valid oops."
+	| oop |
+	"Must mark stack pages first to initialize the per-page trace
+	 flags for full garbage collect before any subsequent tracing."
+	self markAndTraceStackPages: fullGCFlag.
+	self markAndTraceTraceLog.
+	self markAndTracePrimTraceLog.
+	self markAndTrace: specialObjectsOop. "also covers nilObj, trueObj, falseObj, and compact classes"
+	(self isIntegerObject: messageSelector) ifFalse:
+		[self markAndTrace: messageSelector].
+	self markAndTrace: newMethod.
+	self markAndTrace: lkupClass.
+	self traceProfileState.
+	tempOop = 0 ifFalse: [self markAndTrace: tempOop].
+
+	1 to: remapBufferCount do: [:i | 
+			oop := remapBuffer at: i.
+			(self isIntegerObject: oop) ifFalse: [self markAndTrace: oop]].
+
+	"Callback support - trace suspended callback list"
+	1 to: jmpDepth do:[:i|
+		oop := suspendedCallbacks at: i.
+		(self isIntegerObject: oop) ifFalse:[self markAndTrace: oop].
+		oop := suspendedMethods at: i.
+		(self isIntegerObject: oop) ifFalse:[self markAndTrace: oop].
+	]! !
+!StackInterpreter methodsFor: 'plugin primitive support' stamp: 'eem 9/12/2010 06:05' prior: 37788040!
+methodArg: index
+	"Like #stackValue: but access method arguments left-to-right"
+	index > argumentCount + 1 ifTrue:[
+		self cCode: 'fprintf(stderr,"[VM]: Attempt to access method args beyond range\n")'.
+		self printCallStack.
+		self primitiveFail.
+		^0].
+	^self stackValue: argumentCount - index! !
+!StackInterpreter methodsFor: 'plugin primitive support' stamp: 'eem 11/7/2009 11:15' prior: 37788831!
+methodReturnValue: oop
+	"Sets the return value for a method.  In the CoInterpreter we replace the cumbersome
+	 primResult machinery."
+	self pop: argumentCount+1 thenPush: oop.
+	^0! !
+
+StackInterpreter removeSelector: #pluginPop:!
+
+StackInterpreter removeSelector: #pluginPop:thenPush:!
+
+StackInterpreter removeSelector: #pluginPush:!
+
+StackInterpreter removeSelector: #pluginPushBool:!
+
+StackInterpreter removeSelector: #pluginPushFloat:!
+
+StackInterpreter removeSelector: #pluginPushInteger:!
+
+StackInterpreter removeSelector: #pluginStackFloatValue:!
+
+StackInterpreter removeSelector: #pluginStackIntegerValue:!
+
+StackInterpreter removeSelector: #pluginStackObjectValue:!
+
+StackInterpreter removeSelector: #pluginStackValue:!
+!StackInterpreter methodsFor: 'control primitives' stamp: 'eem 9/12/2010 07:16' prior: 38768499!
+primitiveDoPrimitiveWithArgs
+	| argumentArray arraySize index primIdx |
+	argumentArray := self stackTop.
+	(self isArray: argumentArray) ifFalse: [^self primitiveFail].
+	arraySize := self fetchWordLengthOf: argumentArray.
+	self success: (self roomToPushNArgs: arraySize).
+
+	primIdx := self stackIntegerValue: 1.
+	self successful ifFalse: [^self primitiveFail]. "invalid args"
+
+	primitiveFunctionPointer := self functionPointerFor: primIdx inClass: nil.
+	primitiveFunctionPointer = 0 ifTrue:
+		[^self primitiveFail].
+
+	"Pop primIndex and argArray, then push args in place..."
+	self pop: 2.
+	argumentCount := arraySize.
+	index := 1.
+	[index <= argumentCount] whileTrue:
+		[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
+		 index := index + 1].
+
+	self isPrimitiveFunctionPointerAnIndex ifTrue:
+		[self externalQuickPrimitiveResponse.
+		^nil].
+	"We use tempOop instead of pushRemappableOop:/popRemappableOop here because in
+	 the Cogit primitiveEnterCriticalSection, primitiveSignal, primitiveResume et al longjmp back
+	 to either the interpreter or machine code, depending on the process activated.  So if we're
+	 executing one of these primitives control won't actually return here and the matching
+	 popRemappableOop: wouldn't occur, potentially overflowing the remap buffer.  While recursion
+	 could occur (nil tryPrimitive: 118 withArgs: #(111 #())) it counts as shooting oneself in the foot."
+	tempOop := argumentArray. "prim might alloc/gc"
+	lkupClass := nilObj.
+	"Run the primitive (sets primFailCode)"
+	self slowPrimitiveResponse.
+	self successful ifFalse: "If primitive failed, then restore state for failure code"
+		[self pop: arraySize.
+		 self pushInteger: primIdx.
+		 self push: tempOop.
+		 argumentCount := 2].
+	tempOop := 0! !
+!StackInterpreter methodsFor: 'primitive support' stamp: 'eem 9/12/2010 06:21' prior: 38764876!
+slowPrimitiveResponse
+	"Called under the assumption that primFunctionPtr has been preloaded"
+	| nArgs savedFramePointer savedStackPointer |
+	<inline: true>
+	<asmLabel: false>
+	<var: #savedFramePointer type: #'char *'>
+	<var: #savedStackPointer type: #'char *'>
+	FailImbalancedPrimitives ifTrue:
+		[nArgs := argumentCount.
+		 savedStackPointer := stackPointer.
+		 savedFramePointer := framePointer].
+	self initPrimCall.
+	self dispatchFunctionPointer: primitiveFunctionPointer.
+	(FailImbalancedPrimitives
+	and: [self successful
+	and: [framePointer = savedFramePointer]]) ifTrue:"Don't fail if primitive has done something radical, e.g. perform:"
+		[stackPointer ~= (savedStackPointer + (nArgs * BytesPerWord)) ifTrue:
+			[self flag: 'Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context'.
+			 "This is necessary but insufficient; the result may still have been written to the stack.
+			   At least we'll know something is wrong."
+			 stackPointer := savedStackPointer.
+			 self failUnbalancedPrimitive]].
+	"If we are profiling, take accurate primitive measures"
+	nextProfileTick > 0 ifTrue:
+		[self checkProfileTick: newMethod].
+	^self successful! !
+
+(Array streamContents: [ : stream |
+		VMClass withAllSubclassesDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ] !
+
+NewObjectMemory subclass: #StackInterpreter
+	instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue messageSelector argumentCount newMethod primFailCode  primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextPollUsecs nextWakeupUsecs interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag preemptionYields deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth jmpMax suspendedCallbacks suspendedMethods profileProcess profileMethod profileSemaphore nextProfileTick numStackPages desiredNumStackPages desiredEdenBytes metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite'
+	classVariableNames: 'ActiveProcessIndex AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeTable CacheProbeMax CharacterValueIndex ClosureCopiedValuesIndex ClosureIndex CrossedX DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EndOfRun ExcessSignalsIndex FailImbalancedPrimitives FirstLinkIndex HeaderFlagBitPosition LastLinkIndex LiteralStart MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MessageArgumentsIndex MessageDictionaryIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MillisecondClockMask MyListIndex NextLinkIndex PrimitiveExternalCallIndex PrimitiveTable PriorityIndex ProcessListsIndex SelectorStart StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TempFrameStart XIndex YIndex'
+	poolDictionaries: 'VMMethodCacheConstants VMStackFrameOffsets'
+	category: 'VMMaker-Interpreter'!
+
+(Array streamContents: [ : stream |
+		VMClass withAllSubclassesDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ] !
+!CogVMSimulator methodsFor: 'initialization' stamp: 'anon 9/12/2010 08:29' prior: 34997383!
+initialize
+
+	"Initialize the StackInterpreterSimulator when running the interpreter
+	 inside Smalltalk. The primary responsibility of this method is to allocate
+	 Smalltalk Arrays for variables that will be declared as statically-allocated
+	 global arrays in the translated code."
+
+	"initialize class variables"
+	ObjectMemory initBytesPerWord: self bytesPerWord.
+	ObjectMemory initialize.
+	CoInterpreter initialize.
+	Cogit initialize.
+
+	super initialize.
+
+	"Note: we must initialize ConstMinusOne & HasBeenReturnedFromMCPC differently
+	 for simulation, due to the fact that the simulator works only with +ve 32-bit values"
+	ConstMinusOne := self integerObjectOf: -1.
+	HasBeenReturnedFromMCPC := self integerObjectOf: -1.
+	cogit := SimpleStackBasedCogit new setInterpreter: self.
+	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
+	enableCog := true.
+
+	methodCache := Array new: MethodCacheSize.
+	atCache := Array new: AtCacheTotalSize.
+	self flushMethodCache.
+	self flushAtCache.
+	cogCompiledCodeCompactionCalledFor := false.
+	rootTable := Array new: RootTableSize.
+	weakRoots := Array new: WeakRootTableSize.
+	remapBuffer := Array new: RemapBufferSize.
+	gcSemaphoreIndex := 0.
+	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
+	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
+	externalPrimitiveTableFirstFreeIndex := 0.
+	primitiveTable := self class primitiveTable copy.
+	pluginList := #().
+	mappedPluginEntries := OrderedCollection new.
+	desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
+	startMicroseconds := Time totalSeconds * 1000000.
+	maxLiteralCountForCompile := MaxLiteralCountForCompile.
+	flagInterpretedMethods := false.
+
+	"initialize InterpreterSimulator variables used for debugging"
+	byteCount := 0.
+	sendCount := 0.
+	quitBlock := [^ self].
+	traceOn := true.
+	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
+	myBitBlt := BitBltSimulator new setInterpreter: self.
+	filesOpen := OrderedCollection new.
+	headerTypeBytes := CArrayAccessor on: HeaderTypeExtraBytes.
+	transcript := Transcript.
+	displayForm := 'Display has not yet been installed' asDisplayText form.
+	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
+	systemAttributes := Dictionary new.
+	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
+	primTraceLogIndex := 0.
+	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
+	traceLogIndex := 0.
+	traceSources := TraceSources.
+	statCodeCompactionCount := 0.
+	statCodeCompactionUsecs := 0.
+	extSemTabSize := 256! !
+
+Interpreter subclass: #InterpreterSimulator
+	instanceVariableNames: 'byteCount sendCount breakSelector traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView logging printSends'
+	classVariableNames: ''
+	poolDictionaries: ''
+	category: 'VMMaker-InterpreterSimulation'!
+
+NewObjectMemory subclass: #StackInterpreter
+	instanceVariableNames: 'currentBytecode localFP localIP localSP stackLimit stackPage stackPages method instructionPointer stackPointer framePointer localReturnValue messageSelector argumentCount newMethod primFailCode primitiveFunctionPointer methodCache atCache lkupClass highestRunnableProcessPriority nextPollUsecs nextWakeupUsecs interruptKeycode interruptPending savedWindowSize imageHeaderFlags fullScreenFlag preemptionYields deferDisplayUpdates pendingFinalizationSignals extraVMMemory interpreterProxy showSurfaceFn primitiveTable externalPrimitiveTable externalPrimitiveTableFirstFreeIndex overflowedPage extraFramesToMoveOnOverflow globalSessionID jmpBuf jmpDepth jmpMax suspendedCallbacks suspendedMethods profileProcess profileMethod profileSemaphore nextProfileTick numStackPages desiredNumStackPages desiredEdenBytes metaclassSizeBytes interruptCheckChain suppressHeartbeatFlag breakSelector breakSelectorLength longRunningPrimitiveCheckMethod longRunningPrimitiveCheckSemaphore longRunningPrimitiveStartUsecs longRunningPrimitiveStopUsecs longRunningPrimitiveGCUsecs longRunningPrimitiveCheckSequenceNumber longRunningPrimitiveSignalUndelivered tempOop statForceInterruptCheck statStackOverflow statStackPageDivorce statCheckForEvents statProcessSwitch statIOProcessEvents theUnknownShort imageFloatsBigEndian maxExtSemTabSizeSet lastMethodCacheProbeWrite'
+	classVariableNames: 'ActiveProcessIndex AtCacheEntries AtCacheFixedFields AtCacheFmt AtCacheMask AtCacheOop AtCacheSize AtCacheTotalSize AtPutBase BytecodeTable CacheProbeMax CharacterValueIndex ClosureCopiedValuesIndex ClosureIndex CrossedX DirBadPath DirEntryFound DirNoMoreEntries DumpStackOnLowSpace EndOfRun ExcessSignalsIndex FailImbalancedPrimitives FirstLinkIndex HeaderFlagBitPosition LastLinkIndex LiteralStart MaxExternalPrimitiveTableSize MaxJumpBuf MaxPrimitiveIndex MaxQuickPrimitiveIndex MessageArgumentsIndex MessageDictionaryIndex MessageLookupClassIndex MessageSelectorIndex MethodArrayIndex MillisecondClockMask MyListIndex NextLinkIndex PrimitiveExternalCallIndex PrimitiveTable PriorityIndex ProcessListsIndex SelectorStart StreamArrayIndex StreamIndexIndex StreamReadLimitIndex StreamWriteLimitIndex SuperclassIndex SuspendedContextIndex TempFrameStart XIndex YIndex'
+	poolDictionaries: 'VMMethodCacheConstants VMStackFrameOffsets'
+	category: 'VMMaker-Interpreter'!
+
+(Array streamContents: [ : stream |
+		VMClass withAllSubclassesDo: [ :  c |
+			| names |
+			names := c instVarNames.
+			names do: [  : n |
+				((c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsStoreInto: n) isEmpty])
+				and: [
+					c withAllSubclasses allSatisfy: [:sc| (sc whichSelectorsAccess: n) isEmpty]]) ifTrue:
+						[stream nextPut: ((c) -> (n)).
+					]]]])
+
+		sort: [ : a1 : a2 | (a1 key name) <= (a2 key name) ] !
+
+----QUIT----{12 September 2010 . 8:33:24 am} VMMaker-Squeak4.1.image priorSource: 5215404!
+
+----STARTUP----{12 September 2010 . 8:36:52 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Repository user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+	rep user: user;
+	password: pw ]!
+
+"VMMaker"!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Repository user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+	rep user: user;
+	password: pw ]!
+
+----QUIT----{12 September 2010 . 9:06:28 am} VMMaker-Squeak4.1.image priorSource: 5242773!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)

Modified: branches/Cog/platforms/Cross/vm/sqVirtualMachine.c
===================================================================
--- branches/Cog/platforms/Cross/vm/sqVirtualMachine.c	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/platforms/Cross/vm/sqVirtualMachine.c	2010-09-12 16:49:10 UTC (rev 2299)
@@ -8,9 +8,6 @@
 /*** Function prototypes ***/
 
 /* InterpreterProxy methodsFor: 'stack access' */
-/* Disable the new checking interface for the moment for simplicity in Cog */
-#define OLD_PRIM_IFC 1
-#if OLD_PRIM_IFC
 sqInt  pop(sqInt nItems);
 sqInt  popthenPush(sqInt nItems, sqInt oop);
 sqInt  push(sqInt object);
@@ -21,18 +18,6 @@
 sqInt  stackIntegerValue(sqInt offset);
 sqInt  stackObjectValue(sqInt offset);
 sqInt  stackValue(sqInt offset);
-#else
-sqInt  pluginPop(sqInt nItems);
-sqInt  pluginPopthenPush(sqInt nItems, sqInt oop);
-sqInt  pluginPush(sqInt object);
-sqInt  pluginPushBool(sqInt trueOrFalse);
-sqInt  pluginPushFloat(double f);
-sqInt  pluginPushInteger(sqInt integerValue);
-double pluginStackFloatValue(sqInt offset);
-sqInt  pluginStackIntegerValue(sqInt offset);
-sqInt  pluginStackObjectValue(sqInt offset);
-sqInt  pluginStackValue(sqInt offset);
-#endif /* OLD_PRIM_IFC */
 
 /*** variables ***/
 
@@ -253,7 +238,6 @@
 	VM->minorVersion = minorVersion;
 
 	/* InterpreterProxy methodsFor: 'stack access' */
-#if OLD_PRIM_IFC
 	VM->pop = pop;
 	VM->popthenPush = popthenPush;
 	VM->push = push;
@@ -264,18 +248,6 @@
 	VM->stackIntegerValue = stackIntegerValue;
 	VM->stackObjectValue = stackObjectValue;
 	VM->stackValue = stackValue;
-#else
-	VM->pop = pluginPop;
-	VM->popthenPush = pluginPopthenPush;
-	VM->push = pluginPush;
-	VM->pushBool = pluginPushBool;
-	VM->pushFloat = pluginPushFloat;
-	VM->pushInteger = pluginPushInteger;
-	VM->stackFloatValue = pluginStackFloatValue;
-	VM->stackIntegerValue = pluginStackIntegerValue;
-	VM->stackObjectValue = pluginStackObjectValue;
-	VM->stackValue = pluginStackValue;
-#endif
 
 	/* InterpreterProxy methodsFor: 'object access' */
 	VM->argumentCountOf = argumentCountOf;

Modified: branches/Cog/src/vm/cointerp.c
===================================================================
--- branches/Cog/src/vm/cointerp.c	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/src/vm/cointerp.c	2010-09-12 16:49:10 UTC (rev 2299)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
    from
-	CoInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1109,6 +1109,7 @@
 _iss jmp_buf reenterInterpreter;
 _iss sqInt growHeadroom;
 _iss sqInt extraRootCount;
+_iss sqInt tempOop;
 _iss sqInt weakRootCount;
 _iss usqLong nextWakeupUsecs;
 _iss sqInt preemptionYields;
@@ -1124,7 +1125,6 @@
 _iss sqInt lastMethodCacheProbeWrite;
 _iss sqInt lastUncoggableInterpretedBlockMethod;
 _iss sqInt lowSpaceThreshold;
-_iss sqInt primResult;
 _iss usqLong statGCEndUsecs;
 _iss sqInt statSweepCount;
 _iss usqInt compEnd;
@@ -1190,7 +1190,6 @@
 _iss sqInt linkSends;
 _iss usqLong longRunningPrimitiveGCUsecs;
 _iss sqInt overflowLimit;
-_iss sqInt shouldPopArgs;
 _iss long methodCache[MethodCacheSize + 1 /* 4097 */];
 _iss sqInt traceLog[TraceBufferSize /* 768 */];
 _iss sqInt remapBuffer[RemapBufferSize + 1 /* 26 */];
@@ -1202,7 +1201,6 @@
 _iss usqInt suspendedMethods[MaxJumpBuf + 1 /* 33 */];
 _iss sqInt weakRoots[WeakRootTableSize + 1 /* 2626 */];
 _iss jmp_buf jmpBuf[MaxJumpBuf + 1 /* 33 */];
-_iss sqInt byteCodeSizeTable;
 _iss unsigned long byteCount;
 _iss char * stackMemory;
 _iss sqInt theUnknownShort;
@@ -1816,7 +1814,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.26]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.27]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -1845,6 +1843,7 @@
 #define pageIndexForstackBasePlus1bytesPerPage(pointer,stkBasePlus1,pageByteSize) (((char *)(pointer) - (stkBasePlus1)) / (pageByteSize))
 #define primTraceLogIndex(aValue) (GIV(primTraceLogIndex) = (aValue))
 #define printFloat(f) printf("%g", f)
+#define remapBufferCount() GIV(remapBufferCount)
 #define setDesiredCogCodeSize(dccs) (desiredCogCodeSize = (dccs))
 #define stackPageAtpages(index,pages) ((pages) + (index))
 #define typeEtAlWord(cm) (((long *)(cm))[1])
@@ -4866,19 +4865,14 @@
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
 					dispatchFunctionPointer(primitiveFunctionPointer);
-					if (FailImbalancedPrimitives) {
-						if ((GIV(primFailCode) == 0)
-						 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-							if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-								/* Don't fail if primitive has done something radical, e.g. perform: */
-								/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-								/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-								GIV(stackPointer) = savedStackPointer;
-								failUnbalancedPrimitive();
-							}
+					if (FailImbalancedPrimitives
+					 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+						if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+							flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+							GIV(stackPointer) = savedStackPointer;
+							failUnbalancedPrimitive();
 						}
 					}
 					if (GIV(nextProfileTick) > 0) {
@@ -9528,19 +9522,14 @@
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
 			dispatchFunctionPointer(primitiveFunctionPointer);
-			if (FailImbalancedPrimitives) {
-				if ((GIV(primFailCode) == 0)
-				 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-					if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-						/* Don't fail if primitive has done something radical, e.g. perform: */
-						/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-						/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-						GIV(stackPointer) = savedStackPointer;
-						failUnbalancedPrimitive();
-					}
+			if (FailImbalancedPrimitives
+			 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+					flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+					GIV(stackPointer) = savedStackPointer;
+					failUnbalancedPrimitive();
 				}
 			}
 			if (GIV(nextProfileTick) > 0) {
@@ -12342,8 +12331,8 @@
 	if (!(checkOopIntegritynamed(GIV(profileSemaphore), "profileSemaphore"))) {
 		ok = 0;
 	}
-	if (!(GIV(primResult) == 0)) {
-		if (!(checkOopIntegritynamed(GIV(primResult), "primResult"))) {
+	if (!(GIV(tempOop) == 0)) {
+		if (!(checkOopIntegritynamed(GIV(tempOop), "tempOop"))) {
 			ok = 0;
 		}
 	}
@@ -12800,6 +12789,7 @@
 
 	bytes += extraHdrBytes;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 	if (!(sufficientSpaceToAllocate(2500 + bytes))) {
 		return 0;
@@ -14946,19 +14936,14 @@
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
 		dispatchFunctionPointer(primitiveFunctionPointer);
-		if (FailImbalancedPrimitives) {
-			if ((GIV(primFailCode) == 0)
-			 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-					/* Don't fail if primitive has done something radical, e.g. perform: */
-					/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-					/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-					GIV(stackPointer) = savedStackPointer;
-					failUnbalancedPrimitive();
-				}
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
 			}
 		}
 		if (GIV(nextProfileTick) > 0) {
@@ -17960,7 +17945,6 @@
     sqInt i2;
     sqInt i3;
     sqInt oop;
-    sqInt primPops;
 
 	interpreterProxy = sqGetInterpreterProxy();
 	dummyReferToProxy();
@@ -18063,9 +18047,7 @@
 	GIV(profileMethod) = GIV(nilObj);
 	GIV(nextPollUsecs) = 0;
 	GIV(nextWakeupUsecs) = 0;
-	primPops = 0;
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
+	GIV(tempOop) = 0;
 
 	/* cmd-. as used for Mac but no other OS */
 
@@ -18608,6 +18590,7 @@
 	if (newObj1 == 0) {
 		if (hdrSize > 1) {
 			/* begin pushRemappableOop: */
+			assert(addressCouldBeOop(header2));
 			GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = header2;
 		}
 		/* begin allocateChunkAfterGC: */
@@ -19924,8 +19907,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		GIV(longRunningPrimitiveCheckSemaphore) = remap(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		GIV(primResult) = remap(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		GIV(tempOop) = remap(GIV(tempOop));
 	}
 	for (i1 = 1; i1 <= GIV(remapBufferCount); i1 += 1) {
 		oop1 = GIV(remapBuffer)[i1];
@@ -20236,8 +20219,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		markAndTrace(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		markAndTrace(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		markAndTrace(GIV(tempOop));
 	}
 	for (i = 1; i <= GIV(remapBufferCount); i += 1) {
 		oop = GIV(remapBuffer)[i];
@@ -21241,7 +21224,6 @@
 sqInt
 methodArg(sqInt index) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
 	if ((index > GIV(argumentCount)) + 1) {
 		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
 		printCallStack();
@@ -24265,6 +24247,7 @@
 		return;
 	}
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(result));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = result;
 	longAtput(((GIV(remapBuffer)[GIV(remapBufferCount)]) + BaseHeaderSize) + (0 << ShiftForWord), ((runInNOut << 1) | 1));
 	v1 = positive32BitIntegerFor(usecs);
@@ -26605,21 +26588,25 @@
 	}
 	/* begin pushRemappableOop: */
 	oop1 = argumentArray = popStack();
+	assert(addressCouldBeOop(oop1));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop1;
 	/* begin pushRemappableOop: */
 	oop2 = primRcvr = popStack();
+	assert(addressCouldBeOop(oop2));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop2;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop3 = top;
+	assert(addressCouldBeOop(oop3));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop3;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top1 = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop4 = top1;
+	assert(addressCouldBeOop(oop4));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop4;
 	/* begin push: */
 	longAtput(sp5 = GIV(stackPointer) - BytesPerWord, primRcvr);
@@ -26685,7 +26672,6 @@
     sqInt index;
     sqInt integerPointer;
     sqInt nArgs;
-    sqInt oop;
     sqInt primIdx;
     char *savedFramePointer;
     char *savedStackPointer;
@@ -26744,12 +26730,19 @@
 		}
 		return;
 	}
-	/* begin pop: */
-	GIV(stackPointer) += 2 * BytesPerWord;
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primIdx > MaxPrimitiveIndex
 	? 0
 	: primitiveTable[primIdx])));
+	if (primitiveFunctionPointer == 0) {
+		/* begin primitiveFail */
+		if (GIV(primFailCode) == 0) {
+			GIV(primFailCode) = 1;
+		}
+		return;
+	}
+	/* begin pop: */
+	GIV(stackPointer) += 2 * BytesPerWord;
 	GIV(argumentCount) = arraySize;
 	index = 1;
 	while (index <= GIV(argumentCount)) {
@@ -26762,8 +26755,13 @@
 		externalQuickPrimitiveResponse();
 		return;
 	}
-	/* begin pushRemappableOop: */
-	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = argumentArray;
+
+	/* prim might alloc/gc */
+
+	GIV(tempOop) = argumentArray;
+
+	/* Run the primitive (sets primFailCode) */
+
 	GIV(lkupClass) = GIV(nilObj);
 	/* begin slowPrimitiveResponse */
 	if (recordPrimTrace()) {
@@ -26779,19 +26777,14 @@
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
 	dispatchFunctionPointer(primitiveFunctionPointer);
-	if (FailImbalancedPrimitives) {
-		if ((GIV(primFailCode) == 0)
-		 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-				/* Don't fail if primitive has done something radical, e.g. perform: */
-				/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-				/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-				GIV(stackPointer) = savedStackPointer;
-				failUnbalancedPrimitive();
-			}
+	if (FailImbalancedPrimitives
+	 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+		if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+			flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+			GIV(stackPointer) = savedStackPointer;
+			failUnbalancedPrimitive();
 		}
 	}
 	if (GIV(nextProfileTick) > 0) {
@@ -26808,10 +26801,6 @@
 		}
 	}
 	GIV(primFailCode) == 0;
-	/* begin popRemappableOop */
-	oop = GIV(remapBuffer)[GIV(remapBufferCount)];
-	GIV(remapBufferCount) -= 1;
-	argumentArray = oop;
 	if (!(GIV(primFailCode) == 0)) {
 		/* begin pop: */
 		GIV(stackPointer) += arraySize * BytesPerWord;
@@ -26820,10 +26809,11 @@
 		longAtput(sp2 = GIV(stackPointer) - BytesPerWord, ((primIdx << 1) | 1));
 		GIV(stackPointer) = sp2;
 		/* begin push: */
-		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, argumentArray);
+		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(tempOop));
 		GIV(stackPointer) = sp1;
 		GIV(argumentCount) = 2;
 	}
+	GIV(tempOop) = 0;
 }
 
 
@@ -29247,6 +29237,8 @@
 DECL_MAYBE_SQ_GLOBAL_STRUCT
     sqInt i;
     sqInt oldMethod;
+    sqInt primBits;
+    sqInt primIdx;
     sqInt probe;
 
 	oldMethod = longAt(GIV(stackPointer));
@@ -29257,6 +29249,12 @@
 		}
 		probe += MethodCacheEntrySize;
 	}
+	/* begin primitiveIndexOf: */
+	primBits = (((usqInt) (headerOf(oldMethod))) >> 1) & 268435967;
+	primIdx = (primBits & 511) + (((usqInt) primBits) >> 19);
+	if (primIdx == PrimitiveExternalCallIndex) {
+		flushExternalPrimitiveOf(oldMethod);
+	}
 	if (methodHasCogMethod(oldMethod)) {
 		unlinkSendsTo(cogMethodOf(oldMethod));
 	}
@@ -40291,6 +40289,7 @@
 void
 pushRemappableOop(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 }
 
@@ -41976,6 +41975,7 @@
 	voidCogCompiledCode();
 	activeContext = activeContext1;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(activeContext));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = activeContext;
 	activeProc = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
 	/* begin storePointer:ofObject:withValue: */

Modified: branches/Cog/src/vm/cointerp.h
===================================================================
--- branches/Cog/src/vm/cointerp.h	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/src/vm/cointerp.h	2010-09-12 16:49:10 UTC (rev 2299)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
 
 

Modified: branches/Cog/src/vm/gcc3x-cointerp.c
===================================================================
--- branches/Cog/src/vm/gcc3x-cointerp.c	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/src/vm/gcc3x-cointerp.c	2010-09-12 16:49:10 UTC (rev 2299)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
    from
-	CoInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1112,6 +1112,7 @@
 _iss jmp_buf reenterInterpreter;
 _iss sqInt growHeadroom;
 _iss sqInt extraRootCount;
+_iss sqInt tempOop;
 _iss sqInt weakRootCount;
 _iss usqLong nextWakeupUsecs;
 _iss sqInt preemptionYields;
@@ -1127,7 +1128,6 @@
 _iss sqInt lastMethodCacheProbeWrite;
 _iss sqInt lastUncoggableInterpretedBlockMethod;
 _iss sqInt lowSpaceThreshold;
-_iss sqInt primResult;
 _iss usqLong statGCEndUsecs;
 _iss sqInt statSweepCount;
 _iss usqInt compEnd;
@@ -1193,7 +1193,6 @@
 _iss sqInt linkSends;
 _iss usqLong longRunningPrimitiveGCUsecs;
 _iss sqInt overflowLimit;
-_iss sqInt shouldPopArgs;
 _iss long methodCache[MethodCacheSize + 1 /* 4097 */];
 _iss sqInt traceLog[TraceBufferSize /* 768 */];
 _iss sqInt remapBuffer[RemapBufferSize + 1 /* 26 */];
@@ -1205,7 +1204,6 @@
 _iss usqInt suspendedMethods[MaxJumpBuf + 1 /* 33 */];
 _iss sqInt weakRoots[WeakRootTableSize + 1 /* 2626 */];
 _iss jmp_buf jmpBuf[MaxJumpBuf + 1 /* 33 */];
-_iss sqInt byteCodeSizeTable;
 _iss unsigned long byteCount;
 _iss char * stackMemory;
 _iss sqInt theUnknownShort;
@@ -1819,7 +1817,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.26]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.27]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -1848,6 +1846,7 @@
 #define pageIndexForstackBasePlus1bytesPerPage(pointer,stkBasePlus1,pageByteSize) (((char *)(pointer) - (stkBasePlus1)) / (pageByteSize))
 #define primTraceLogIndex(aValue) (GIV(primTraceLogIndex) = (aValue))
 #define printFloat(f) printf("%g", f)
+#define remapBufferCount() GIV(remapBufferCount)
 #define setDesiredCogCodeSize(dccs) (desiredCogCodeSize = (dccs))
 #define stackPageAtpages(index,pages) ((pages) + (index))
 #define typeEtAlWord(cm) (((long *)(cm))[1])
@@ -4870,19 +4869,14 @@
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
 					dispatchFunctionPointer(primitiveFunctionPointer);
-					if (FailImbalancedPrimitives) {
-						if ((GIV(primFailCode) == 0)
-						 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-							if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-								/* Don't fail if primitive has done something radical, e.g. perform: */
-								/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-								/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-								GIV(stackPointer) = savedStackPointer;
-								failUnbalancedPrimitive();
-							}
+					if (FailImbalancedPrimitives
+					 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+						if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+							flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+							GIV(stackPointer) = savedStackPointer;
+							failUnbalancedPrimitive();
 						}
 					}
 					if (GIV(nextProfileTick) > 0) {
@@ -9532,19 +9526,14 @@
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
 			dispatchFunctionPointer(primitiveFunctionPointer);
-			if (FailImbalancedPrimitives) {
-				if ((GIV(primFailCode) == 0)
-				 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-					if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-						/* Don't fail if primitive has done something radical, e.g. perform: */
-						/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-						/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-						GIV(stackPointer) = savedStackPointer;
-						failUnbalancedPrimitive();
-					}
+			if (FailImbalancedPrimitives
+			 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+					flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+					GIV(stackPointer) = savedStackPointer;
+					failUnbalancedPrimitive();
 				}
 			}
 			if (GIV(nextProfileTick) > 0) {
@@ -12346,8 +12335,8 @@
 	if (!(checkOopIntegritynamed(GIV(profileSemaphore), "profileSemaphore"))) {
 		ok = 0;
 	}
-	if (!(GIV(primResult) == 0)) {
-		if (!(checkOopIntegritynamed(GIV(primResult), "primResult"))) {
+	if (!(GIV(tempOop) == 0)) {
+		if (!(checkOopIntegritynamed(GIV(tempOop), "tempOop"))) {
 			ok = 0;
 		}
 	}
@@ -12804,6 +12793,7 @@
 
 	bytes += extraHdrBytes;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 	if (!(sufficientSpaceToAllocate(2500 + bytes))) {
 		return 0;
@@ -14950,19 +14940,14 @@
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
 		dispatchFunctionPointer(primitiveFunctionPointer);
-		if (FailImbalancedPrimitives) {
-			if ((GIV(primFailCode) == 0)
-			 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-					/* Don't fail if primitive has done something radical, e.g. perform: */
-					/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-					/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-					GIV(stackPointer) = savedStackPointer;
-					failUnbalancedPrimitive();
-				}
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
 			}
 		}
 		if (GIV(nextProfileTick) > 0) {
@@ -17964,7 +17949,6 @@
     sqInt i2;
     sqInt i3;
     sqInt oop;
-    sqInt primPops;
 
 	interpreterProxy = sqGetInterpreterProxy();
 	dummyReferToProxy();
@@ -18067,9 +18051,7 @@
 	GIV(profileMethod) = GIV(nilObj);
 	GIV(nextPollUsecs) = 0;
 	GIV(nextWakeupUsecs) = 0;
-	primPops = 0;
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
+	GIV(tempOop) = 0;
 
 	/* cmd-. as used for Mac but no other OS */
 
@@ -18612,6 +18594,7 @@
 	if (newObj1 == 0) {
 		if (hdrSize > 1) {
 			/* begin pushRemappableOop: */
+			assert(addressCouldBeOop(header2));
 			GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = header2;
 		}
 		/* begin allocateChunkAfterGC: */
@@ -19928,8 +19911,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		GIV(longRunningPrimitiveCheckSemaphore) = remap(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		GIV(primResult) = remap(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		GIV(tempOop) = remap(GIV(tempOop));
 	}
 	for (i1 = 1; i1 <= GIV(remapBufferCount); i1 += 1) {
 		oop1 = GIV(remapBuffer)[i1];
@@ -20240,8 +20223,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		markAndTrace(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		markAndTrace(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		markAndTrace(GIV(tempOop));
 	}
 	for (i = 1; i <= GIV(remapBufferCount); i += 1) {
 		oop = GIV(remapBuffer)[i];
@@ -21245,7 +21228,6 @@
 sqInt
 methodArg(sqInt index) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
 	if ((index > GIV(argumentCount)) + 1) {
 		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
 		printCallStack();
@@ -24269,6 +24251,7 @@
 		return;
 	}
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(result));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = result;
 	longAtput(((GIV(remapBuffer)[GIV(remapBufferCount)]) + BaseHeaderSize) + (0 << ShiftForWord), ((runInNOut << 1) | 1));
 	v1 = positive32BitIntegerFor(usecs);
@@ -26609,21 +26592,25 @@
 	}
 	/* begin pushRemappableOop: */
 	oop1 = argumentArray = popStack();
+	assert(addressCouldBeOop(oop1));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop1;
 	/* begin pushRemappableOop: */
 	oop2 = primRcvr = popStack();
+	assert(addressCouldBeOop(oop2));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop2;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop3 = top;
+	assert(addressCouldBeOop(oop3));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop3;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top1 = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop4 = top1;
+	assert(addressCouldBeOop(oop4));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop4;
 	/* begin push: */
 	longAtput(sp5 = GIV(stackPointer) - BytesPerWord, primRcvr);
@@ -26689,7 +26676,6 @@
     sqInt index;
     sqInt integerPointer;
     sqInt nArgs;
-    sqInt oop;
     sqInt primIdx;
     char *savedFramePointer;
     char *savedStackPointer;
@@ -26748,12 +26734,19 @@
 		}
 		return;
 	}
-	/* begin pop: */
-	GIV(stackPointer) += 2 * BytesPerWord;
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primIdx > MaxPrimitiveIndex
 	? 0
 	: primitiveTable[primIdx])));
+	if (primitiveFunctionPointer == 0) {
+		/* begin primitiveFail */
+		if (GIV(primFailCode) == 0) {
+			GIV(primFailCode) = 1;
+		}
+		return;
+	}
+	/* begin pop: */
+	GIV(stackPointer) += 2 * BytesPerWord;
 	GIV(argumentCount) = arraySize;
 	index = 1;
 	while (index <= GIV(argumentCount)) {
@@ -26766,8 +26759,13 @@
 		externalQuickPrimitiveResponse();
 		return;
 	}
-	/* begin pushRemappableOop: */
-	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = argumentArray;
+
+	/* prim might alloc/gc */
+
+	GIV(tempOop) = argumentArray;
+
+	/* Run the primitive (sets primFailCode) */
+
 	GIV(lkupClass) = GIV(nilObj);
 	/* begin slowPrimitiveResponse */
 	if (recordPrimTrace()) {
@@ -26783,19 +26781,14 @@
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
 	dispatchFunctionPointer(primitiveFunctionPointer);
-	if (FailImbalancedPrimitives) {
-		if ((GIV(primFailCode) == 0)
-		 && ((GIV(framePointer) == savedFramePointer)
- && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase)))) {
-			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-				/* Don't fail if primitive has done something radical, e.g. perform: */
-				/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-				/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-				GIV(stackPointer) = savedStackPointer;
-				failUnbalancedPrimitive();
-			}
+	if (FailImbalancedPrimitives
+	 && ((GIV(primFailCode) == 0)
+ && ((GIV(framePointer) == savedFramePointer)
+ && (!((((usqInt)(longAt(GIV(framePointer) + FoxMethod)))) < heapBase))))) {
+		if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+			flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+			GIV(stackPointer) = savedStackPointer;
+			failUnbalancedPrimitive();
 		}
 	}
 	if (GIV(nextProfileTick) > 0) {
@@ -26812,10 +26805,6 @@
 		}
 	}
 	GIV(primFailCode) == 0;
-	/* begin popRemappableOop */
-	oop = GIV(remapBuffer)[GIV(remapBufferCount)];
-	GIV(remapBufferCount) -= 1;
-	argumentArray = oop;
 	if (!(GIV(primFailCode) == 0)) {
 		/* begin pop: */
 		GIV(stackPointer) += arraySize * BytesPerWord;
@@ -26824,10 +26813,11 @@
 		longAtput(sp2 = GIV(stackPointer) - BytesPerWord, ((primIdx << 1) | 1));
 		GIV(stackPointer) = sp2;
 		/* begin push: */
-		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, argumentArray);
+		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(tempOop));
 		GIV(stackPointer) = sp1;
 		GIV(argumentCount) = 2;
 	}
+	GIV(tempOop) = 0;
 }
 
 
@@ -29251,6 +29241,8 @@
 DECL_MAYBE_SQ_GLOBAL_STRUCT
     sqInt i;
     sqInt oldMethod;
+    sqInt primBits;
+    sqInt primIdx;
     sqInt probe;
 
 	oldMethod = longAt(GIV(stackPointer));
@@ -29261,6 +29253,12 @@
 		}
 		probe += MethodCacheEntrySize;
 	}
+	/* begin primitiveIndexOf: */
+	primBits = (((usqInt) (headerOf(oldMethod))) >> 1) & 268435967;
+	primIdx = (primBits & 511) + (((usqInt) primBits) >> 19);
+	if (primIdx == PrimitiveExternalCallIndex) {
+		flushExternalPrimitiveOf(oldMethod);
+	}
 	if (methodHasCogMethod(oldMethod)) {
 		unlinkSendsTo(cogMethodOf(oldMethod));
 	}
@@ -40295,6 +40293,7 @@
 void
 pushRemappableOop(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 }
 
@@ -41980,6 +41979,7 @@
 	voidCogCompiledCode();
 	activeContext = activeContext1;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(activeContext));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = activeContext;
 	activeProc = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
 	/* begin storePointer:ofObject:withValue: */

Modified: branches/Cog/src/vm/interp.h
===================================================================
--- branches/Cog/src/vm/interp.h	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/src/vm/interp.h	2010-09-12 16:49:10 UTC (rev 2299)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
 
 #define COGVM 1

Modified: branches/Cog/stacksrc/vm/gcc3x-interp.c
===================================================================
--- branches/Cog/stacksrc/vm/gcc3x-interp.c	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/stacksrc/vm/gcc3x-interp.c	2010-09-12 16:49:10 UTC (rev 2299)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
    from
-	StackInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
-static char __buildInfo[] = "StackInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -142,7 +142,6 @@
 #define CrossedX 258
 #define CtxtTempFrameStart 6
 #define DoAssertionChecks 0
-#define DoBalanceChecks 0
 #define DoExpensiveAssertionChecks 0
 #define Done 4
 #define DumpStackOnLowSpace 0
@@ -513,16 +512,6 @@
 static sqInt oopisGreaterThanandLessThan(sqInt anOop, sqInt baseOop, sqInt limitOop);
 static sqInt pageIndexFor(void *pointer);
 static sqInt pageListIsWellFormed(void);
-void pluginPop(sqInt nItems);
-void pluginPopthenPush(sqInt nItems, sqInt oop);
-void pluginPushBool(sqInt trueOrFalse);
-void pluginPushFloat(double  f);
-void pluginPushInteger(sqInt integerValue);
-void pluginPush(sqInt oop);
-double pluginStackFloatValue(sqInt index);
-sqInt pluginStackIntegerValue(sqInt index);
-sqInt pluginStackObjectValue(sqInt index);
-sqInt pluginStackValue(sqInt index);
 sqInt popRemappableOop(void);
 static sqInt popStack(void);
 sqInt pop(sqInt nItems);
@@ -784,7 +773,6 @@
 void printStackPagesInUse(void);
 static void printStackPage(StackPage *page);
 static void printStringOf(sqInt oop);
-static void printUnbalancedStack(sqInt primIdx);
 void print(char *s);
 void pushBool(sqInt trueOrFalse);
 static sqInt pushedReceiverOrClosureOfFrame(char *theFP);
@@ -832,7 +820,6 @@
 static sqInt sizeOfFree(sqInt oop);
 sqInt sizeOfSTArrayFromCPrimitive(void *cPtr);
 sqInt slotSizeOf(sqInt oop);
-static sqInt slowPrimitiveResponse(void);
 static void snapshot(sqInt embedded);
 static void space(void);
 sqInt splObj(sqInt index);
@@ -892,8 +879,8 @@
 _iss sqInt specialObjectsOop;
 _iss StackPage * stackPage;
 _iss char * framePointer;
-_iss usqInt method;
 _iss sqInt nilObj;
+_iss usqInt method;
 _iss usqInt freeStart;
 _iss sqInt argumentCount;
 _iss usqInt youngStart;
@@ -903,11 +890,8 @@
 _iss sqInt trueObj;
 _iss sqInt falseObj;
 _iss usqInt instructionPointer;
-_iss sqInt remapBufferCount;
 _iss usqInt newMethod;
-_iss sqInt primPops;
-_iss sqInt primResult;
-_iss sqInt shouldPopArgs;
+_iss sqInt remapBufferCount;
 _iss usqInt reserveStart;
 _iss StackPage * pages;
 _iss char * stackLimit;
@@ -915,23 +899,24 @@
 _iss char * stackMemory;
 _iss sqInt bytesPerPage;
 _iss usqInt memoryLimit;
+_iss sqLong nextProfileTick;
 _iss StackPage * mostRecentlyUsedPage;
 _iss sqInt needGCFlag;
 _iss usqInt scavengeThreshold;
 _iss usqInt fwdTableNext;
 _iss sqInt jmpDepth;
+_iss sqInt profileProcess;
 _iss sqInt numStackPages;
+_iss sqInt profileMethod;
 _iss usqInt compStart;
 _iss sqInt numPages;
 _iss sqInt growHeadroom;
-_iss sqInt profileProcess;
 _iss sqInt extraRootCount;
+_iss sqInt tempOop;
 _iss sqInt weakRootCount;
 _iss sqInt longRunningPrimitiveCheckSemaphore;
-_iss sqLong nextProfileTick;
 _iss usqLong nextWakeupUsecs;
 _iss sqInt preemptionYields;
-_iss sqInt profileMethod;
 _iss sqInt highestRunnableProcessPriority;
 _iss sqInt longRunningPrimitiveCheckMethod;
 _iss usqLong longRunningPrimitiveStartUsecs;
@@ -1007,7 +992,6 @@
 _iss sqInt weakRoots[WeakRootTableSize + 1 /* 2626 */];
 _iss jmp_buf jmpBuf[MaxJumpBuf + 1 /* 33 */];
 _iss unsigned long byteCount;
-_iss sqInt pageMap;
 #undef _iss
 #if SQ_USE_GLOBAL_STRUCT
  } fum;
@@ -1615,7 +1599,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.26]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.27]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -1626,6 +1610,7 @@
 #define mostRecentlyUsedPage() GIV(mostRecentlyUsedPage)
 #define pageIndexForstackMemorybytesPerPage(pointer,stackmem,pageByteSize) (((char *)(pointer) - (stackmem) - 1) / (pageByteSize))
 #define printFloat(f) printf("%g", f)
+#define remapBufferCount() GIV(remapBufferCount)
 #define stackPageAtpages(index,pages) ((pages) + (index))
 
 
@@ -4317,6 +4302,9 @@
 				sqInt succeeded;
 				sqInt localPrimIndex;
 				sqInt oop;
+				sqInt nArgs;
+				char *savedFramePointer;
+				char *savedStackPointer;
 				sqInt errorCode;
 				sqInt i;
 				sqInt methodHeader;
@@ -4324,6 +4312,7 @@
 				sqInt rcvr;
 				sqInt table;
 				sqInt object;
+				sqInt aPrimitiveMethod;
 
 				VM_LABEL(0commonSend);
 								sendBreakpointreceiver(GIV(messageSelector) + BaseHeaderSize, lengthOf(GIV(messageSelector)), longAtPointer(localSP + (GIV(argumentCount) * BytesPerWord)));
@@ -4420,7 +4409,38 @@
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
 					GIV(framePointer) = localFP;
-					succeeded = slowPrimitiveResponse();
+					/* begin slowPrimitiveResponse */
+					if (FailImbalancedPrimitives) {
+						nArgs = GIV(argumentCount);
+						savedStackPointer = GIV(stackPointer);
+						savedFramePointer = GIV(framePointer);
+					}
+					/* begin initPrimCall */
+					GIV(primFailCode) = 0;
+					dispatchFunctionPointer(primitiveFunctionPointer);
+					if (FailImbalancedPrimitives
+					 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+						if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+							flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+							GIV(stackPointer) = savedStackPointer;
+							failUnbalancedPrimitive();
+						}
+					}
+					if (GIV(nextProfileTick) > 0) {
+						/* begin checkProfileTick: */
+						aPrimitiveMethod = GIV(newMethod);
+						assert(GIV(nextProfileTick) != 0);
+						if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+							GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+							GIV(profileMethod) = (GIV(primFailCode) == 0
+								? aPrimitiveMethod
+								: GIV(nilObj));
+							forceInterruptCheck();
+							GIV(nextProfileTick) = 0;
+						}
+					}
+					succeeded = GIV(primFailCode) == 0;
 					/* begin internalizeIPandSP */
 					localIP = pointerForOop(GIV(instructionPointer));
 					localSP = pointerForOop(GIV(stackPointer));
@@ -5334,12 +5354,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -5522,12 +5536,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -5756,12 +5764,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatLess:thanArg: */
 				VM_LABEL(0primitiveFloatLessthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6025,12 +6027,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatGreater:thanArg: */
 				VM_LABEL(0primitiveFloatGreaterthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6294,12 +6290,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatGreater:thanArg: */
 				VM_LABEL(1primitiveFloatGreaterthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6563,12 +6553,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatLess:thanArg: */
 				VM_LABEL(1primitiveFloatLessthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6831,12 +6815,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatEqual:toArg: */
 				VM_LABEL(0primitiveFloatEqualtoArg);
 				/* begin loadFloatOrIntFrom: */
@@ -7099,12 +7077,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatEqual:toArg: */
 				VM_LABEL(1primitiveFloatEqualtoArg);
 				/* begin loadFloatOrIntFrom: */
@@ -7326,12 +7298,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -7522,12 +7488,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -7697,12 +7657,6 @@
 				VM_LABEL(0bytecodePrimMod);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				mod = doPrimitiveModby(longAtPointer(localSP + (1 * BytesPerWord)), longAtPointer(localSP + (0 * BytesPerWord)));
 				if (GIV(primFailCode) == 0) {
 					/* begin internalPop:thenPush: */
@@ -7732,12 +7686,6 @@
 				VM_LABEL(0bytecodePrimMakePoint);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -7835,12 +7783,6 @@
 				VM_LABEL(0bytecodePrimBitShift);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -7941,12 +7883,6 @@
 				VM_LABEL(0bytecodePrimDiv);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				quotient = doPrimitiveDivby(longAtPointer(localSP + (1 * BytesPerWord)), longAtPointer(localSP + (0 * BytesPerWord)));
 				if (GIV(primFailCode) == 0) {
 					/* begin internalPop:thenPush: */
@@ -7977,12 +7913,6 @@
 				VM_LABEL(0bytecodePrimBitAnd);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -8041,12 +7971,6 @@
 				VM_LABEL(0bytecodePrimBitOr);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -8267,13 +8191,7 @@
 				VM_LABEL(0bytecodePrimSize);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
 
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
-
 				/* Shortcut the mega-lookup for ByteString and Array, the two big consumers of cycles
 	 here. Both of these have compact class indices and neither has any added fields. */
 
@@ -8521,12 +8439,6 @@
 								block = longAtPointer(localSP);
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				GIV(argumentCount) = 0;
 				/* begin assertClassOf:is: */
 				if ((block & 1)) {
@@ -8593,12 +8505,6 @@
 								block = longAtPointer(localSP + (1 * BytesPerWord));
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				GIV(argumentCount) = 1;
 				/* begin assertClassOf:is: */
 				if ((block & 1)) {
@@ -8697,12 +8603,6 @@
 				VM_LABEL(0bytecodePrimPointX);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				rcvr = longAtPointer(localSP);
 				/* begin assertClassOf:is: */
 				if ((rcvr & 1)) {
@@ -8760,12 +8660,6 @@
 				VM_LABEL(0bytecodePrimPointY);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				rcvr = longAtPointer(localSP);
 				/* begin assertClassOf:is: */
 				if ((rcvr & 1)) {
@@ -9730,12 +9624,6 @@
 	GIV(jmpDepth) -= 1;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	return 1;
 }
 
@@ -10275,8 +10163,8 @@
 	if (!(checkOopIntegritynamed(GIV(profileSemaphore), "profileSemaphore"))) {
 		ok = 0;
 	}
-	if (!(GIV(primResult) == 0)) {
-		if (!(checkOopIntegritynamed(GIV(primResult), "primResult"))) {
+	if (!(GIV(tempOop) == 0)) {
+		if (!(checkOopIntegritynamed(GIV(tempOop), "tempOop"))) {
 			ok = 0;
 		}
 	}
@@ -10635,6 +10523,7 @@
 
 	bytes += extraHdrBytes;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 	if (!(sufficientSpaceToAllocate(2500 + bytes))) {
 		return 0;
@@ -10708,12 +10597,6 @@
 	value = longAt(GIV(stackPointer));
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (2 * BytesPerWord));
 	if (!((rcvr & 1) == 0)) {
 		GIV(primFailCode) = PrimErrInappropriate; return;
@@ -10805,12 +10688,6 @@
 	}
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	if (stringy) {
 		stObjectatput(rcvr, index, asciiOfCharacter(value));
 	}
@@ -10847,12 +10724,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (1 * BytesPerWord));
 	if (!((rcvr & 1) == 0)) {
 		GIV(primFailCode) = PrimErrInappropriate; return;
@@ -10921,12 +10792,6 @@
 	}
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	result = stObjectat(rcvr, index);
 	if (GIV(primFailCode) == 0) {
 		if (stringy) {
@@ -14676,9 +14541,7 @@
 	GIV(profileMethod) = GIV(nilObj);
 	GIV(nextPollUsecs) = 0;
 	GIV(nextWakeupUsecs) = 0;
-	GIV(primPops) = 0;
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
+	GIV(tempOop) = 0;
 
 	/* cmd-. as used for Mac but no other OS */
 
@@ -15247,6 +15110,7 @@
 	if (newObj1 == 0) {
 		if (hdrSize > 1) {
 			/* begin pushRemappableOop: */
+			assert(addressCouldBeOop(header2));
 			GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = header2;
 		}
 		/* begin allocateChunkAfterGC: */
@@ -16329,8 +16193,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		GIV(longRunningPrimitiveCheckSemaphore) = remap(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		GIV(primResult) = remap(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		GIV(tempOop) = remap(GIV(tempOop));
 	}
 	for (i1 = 1; i1 <= GIV(remapBufferCount); i1 += 1) {
 		oop1 = GIV(remapBuffer)[i1];
@@ -16545,8 +16409,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		markAndTrace(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		markAndTrace(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		markAndTrace(GIV(tempOop));
 	}
 	for (i = 1; i <= GIV(remapBufferCount); i += 1) {
 		oop = GIV(remapBuffer)[i];
@@ -17364,7 +17228,6 @@
 sqInt
 methodArg(sqInt index) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
 	if ((index > GIV(argumentCount)) + 1) {
 		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
 		printCallStack();
@@ -17395,17 +17258,17 @@
 }
 
 
-/*	Stores the return value from a primitive */
+/*	Sets the return value for a method. In the CoInterpreter we replace the
+	cumbersome primResult machinery. */
 
 sqInt
 methodReturnValue(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if (!(GIV(primResult) == 0)) {
-		fprintf(stderr, "[VM]: Attempt to set method return type multiple times\n");
-		printCallStack();
-	}
-	GIV(shouldPopArgs) = 1;
-	GIV(primResult) = oop;
+    char *sp;
+
+	/* begin pop:thenPush: */
+	longAtput(sp = GIV(stackPointer) + (((GIV(argumentCount) + 1) - 1) * BytesPerWord), oop);
+	GIV(stackPointer) = sp;
 	return 0;
 }
 
@@ -18092,278 +17955,6 @@
 }
 
 
-/*	The (obsolete) interface used by primitives that doesn't actually do
-	anything besides noting the fact someone tried to pop the given number of
-	elements 
- */
-
-void
-pluginPop(sqInt nItems) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
-	GIV(primPops) += nItems;
-}
-
-
-/*	A variant of pop:thenPush: used by primitives that doesn't actually do
-	anything besides noting the fact someone tried to pop the given number of
-	elements 
- */
-
-void
-pluginPopthenPush(sqInt nItems, sqInt oop) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	/* begin pluginPop: */
-	GIV(shouldPopArgs) = 1;
-	GIV(primPops) += nItems;
-	/* begin pluginPush: */
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushBool(sqInt trueOrFalse) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if (trueOrFalse) {
-		/* begin pluginPush: */
-
-		/* a push counts as a negative pop */
-
-		GIV(primPops) -= 1;
-		methodReturnValue(GIV(trueObj));
-	}
-	else {
-		/* begin pluginPush: */
-
-		/* a push counts as a negative pop */
-
-		GIV(primPops) -= 1;
-		methodReturnValue(GIV(falseObj));
-	}
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushFloat(double  f) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt oop;
-
-	/* begin pluginPush: */
-	oop = floatObjectOf(f);
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushInteger(sqInt integerValue) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	/* begin pluginPush: */
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(((integerValue << 1) | 1));
-}
-
-
-/*	A variant of push: used by primitives to communicate the return value */
-
-void
-pluginPush(sqInt oop) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only. */
-
-double
-pluginStackFloatValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt ccIndex;
-    sqInt floatPointer;
-    double result;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackFloatValue: */
-
-	/* N.B.  Because Slang always inlines assertClassOf:is:compactClassIndex:
-	 (because assertClassOf:is:compactClassIndex: has an inline: pragma) the
-	 phrase (self splObj: ClassArray) is expanded in-place and is _not_
-	 evaluated if ClassArrayCompactIndex is non-zero. */
-
-	floatPointer = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(23assertClassOfiscompactClassIndex);
-	if ((floatPointer & 1)) {
-		/* begin success: */
-		if (!(0)) {
-			if (GIV(primFailCode) == 0) {
-
-				/* Don't overwrite an error code that has already been set. */
-
-				GIV(primFailCode) = 1;
-			}
-		}
-		goto l1;
-	}
-	ccIndex = (((usqInt) (longAt(floatPointer))) >> 12) & 31;
-	if (ClassFloatCompactIndex == 0) {
-		if (ccIndex == 0) {
-			/* begin success: */
-			if (!(((longAt(floatPointer - BaseHeaderSize)) & AllButTypeMask) == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassFloat << ShiftForWord))))) {
-				if (GIV(primFailCode) == 0) {
-
-					/* Don't overwrite an error code that has already been set. */
-
-					GIV(primFailCode) = 1;
-				}
-			}
-		}
-		else {
-			/* begin success: */
-			if (!(0)) {
-				if (GIV(primFailCode) == 0) {
-
-					/* Don't overwrite an error code that has already been set. */
-
-					GIV(primFailCode) = 1;
-				}
-			}
-		}
-	}
-	else {
-		/* begin success: */
-		if (!(ClassFloatCompactIndex == ccIndex)) {
-			if (GIV(primFailCode) == 0) {
-
-				/* Don't overwrite an error code that has already been set. */
-
-				GIV(primFailCode) = 1;
-			}
-		}
-	}
-l1:	/* end assertClassOf:is:compactClassIndex: */;
-	if (GIV(primFailCode) == 0) {
-		;
-		fetchFloatAtinto(floatPointer + BaseHeaderSize, result);
-		return result;
-	}
-	else {
-		return 0.0;
-	}
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackIntegerValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt integerPointer;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackIntegerValue: */
-	integerPointer = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	/* begin checkedIntegerValueOf: */
-	if ((integerPointer & 1)) {
-		return (integerPointer >> 1);
-	}
-	else {
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackObjectValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt oop;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackObjectValue: */
-	oop = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	if ((oop & 1)) {
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return null;
-	}
-	return oop;
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	return longAt(GIV(stackPointer) + (index * BytesPerWord));
-}
-
-
 /*	Pop and return the possibly remapped object from the remap buffer. */
 
 sqInt
@@ -18468,7 +18059,7 @@
 		return value;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(24assertClassOfiscompactClassIndex);
+	VM_LABEL(23assertClassOfiscompactClassIndex);
 	if ((oop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -19091,7 +18682,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(25assertClassOfiscompactClassIndex);
+	VM_LABEL(24assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -20298,6 +19889,7 @@
 		return;
 	}
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(result));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = result;
 	longAtput(((GIV(remapBuffer)[GIV(remapBufferCount)]) + BaseHeaderSize) + (0 << ShiftForWord), ((runInNOut << 1) | 1));
 	v1 = positive32BitIntegerFor(usecs);
@@ -22111,7 +21703,7 @@
 		GIV(primFailCode) = -3; return;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(26assertClassOfiscompactClassIndex);
+	VM_LABEL(25assertClassOfiscompactClassIndex);
 	oop9 = spec = longAt((methodArg + BaseHeaderSize) + (1 << ShiftForWord));
 	if ((oop9 & 1)) {
 		/* begin success: */
@@ -22255,21 +21847,25 @@
 	}
 	/* begin pushRemappableOop: */
 	oop1 = argumentArray = popStack();
+	assert(addressCouldBeOop(oop1));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop1;
 	/* begin pushRemappableOop: */
 	oop2 = primRcvr = popStack();
+	assert(addressCouldBeOop(oop2));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop2;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop3 = top;
+	assert(addressCouldBeOop(oop3));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop3;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top1 = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop4 = top1;
+	assert(addressCouldBeOop(oop4));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop4;
 	/* begin push: */
 	longAtput(sp5 = GIV(stackPointer) - BytesPerWord, primRcvr);
@@ -22328,14 +21924,17 @@
 static void
 primitiveDoPrimitiveWithArgs(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt argumentArray;
     sqInt arraySize;
     sqInt cntxSize;
     sqInt header;
     sqInt index;
     sqInt integerPointer;
-    sqInt oop;
+    sqInt nArgs;
     sqInt primIdx;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22397,12 +21996,19 @@
 		}
 		return;
 	}
-	/* begin pop: */
-	GIV(stackPointer) += 2 * BytesPerWord;
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primIdx > MaxPrimitiveIndex
 	? 0
 	: primitiveTable[primIdx])));
+	if (primitiveFunctionPointer == 0) {
+		/* begin primitiveFail */
+		if (GIV(primFailCode) == 0) {
+			GIV(primFailCode) = 1;
+		}
+		return;
+	}
+	/* begin pop: */
+	GIV(stackPointer) += 2 * BytesPerWord;
 	GIV(argumentCount) = arraySize;
 	index = 1;
 	while (index <= GIV(argumentCount)) {
@@ -22415,14 +22021,46 @@
 		externalQuickPrimitiveResponse();
 		return;
 	}
-	/* begin pushRemappableOop: */
-	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = argumentArray;
+
+	/* prim might alloc/gc */
+
+	GIV(tempOop) = argumentArray;
+
+	/* Run the primitive (sets primFailCode) */
+
 	GIV(lkupClass) = GIV(nilObj);
-	slowPrimitiveResponse();
-	/* begin popRemappableOop */
-	oop = GIV(remapBuffer)[GIV(remapBufferCount)];
-	GIV(remapBufferCount) -= 1;
-	argumentArray = oop;
+	/* begin slowPrimitiveResponse */
+	if (FailImbalancedPrimitives) {
+		nArgs = GIV(argumentCount);
+		savedStackPointer = GIV(stackPointer);
+		savedFramePointer = GIV(framePointer);
+	}
+	/* begin initPrimCall */
+	GIV(primFailCode) = 0;
+	dispatchFunctionPointer(primitiveFunctionPointer);
+	if (FailImbalancedPrimitives
+	 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+		if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+			flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+			GIV(stackPointer) = savedStackPointer;
+			failUnbalancedPrimitive();
+		}
+	}
+	if (GIV(nextProfileTick) > 0) {
+		/* begin checkProfileTick: */
+		aPrimitiveMethod = GIV(newMethod);
+		assert(GIV(nextProfileTick) != 0);
+		if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+			GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+			GIV(profileMethod) = (GIV(primFailCode) == 0
+				? aPrimitiveMethod
+				: GIV(nilObj));
+			forceInterruptCheck();
+			GIV(nextProfileTick) = 0;
+		}
+	}
+	GIV(primFailCode) == 0;
 	if (!(GIV(primFailCode) == 0)) {
 		/* begin pop: */
 		GIV(stackPointer) += arraySize * BytesPerWord;
@@ -22431,10 +22069,11 @@
 		longAtput(sp2 = GIV(stackPointer) - BytesPerWord, ((primIdx << 1) | 1));
 		GIV(stackPointer) = sp2;
 		/* begin push: */
-		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, argumentArray);
+		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(tempOop));
 		GIV(stackPointer) = sp1;
 		GIV(argumentCount) = 2;
 	}
+	GIV(tempOop) = 0;
 }
 
 
@@ -22572,17 +22211,20 @@
 static void
 primitiveExecuteMethod(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt errorCode;
     sqInt i;
     sqInt methodArgument;
     sqInt methodHeader;
-    sqInt methodPointer;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
     sqInt primBits;
     sqInt primitiveIndex;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22606,8 +22248,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	GIV(newMethod) = ((sqInt) top);
 	/* begin primitiveIndexOf: */
-	methodPointer = GIV(newMethod);
-	primBits = (((usqInt) (longAt((methodPointer + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primBits = (((usqInt) (longAt((GIV(newMethod) + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
 	primitiveIndex = (primBits & 511) + (((usqInt) primBits) >> 19);
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primitiveIndex > MaxPrimitiveIndex
@@ -22615,12 +22256,44 @@
 	: primitiveTable[primitiveIndex])));
 	GIV(argumentCount) -= 1;
 	/* begin executeNewMethod */
+	VM_LABEL(0executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -22700,12 +22373,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 }
 
 
@@ -22718,6 +22385,7 @@
 static void
 primitiveExecuteMethodArgsArray(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt argCnt;
     sqInt argumentArray;
     sqInt errorCode;
@@ -22725,13 +22393,15 @@
     sqInt i1;
     sqInt methodArgument;
     sqInt methodHeader;
-    sqInt methodPointer;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
     sqInt primBits;
     sqInt primitiveIndex;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22763,8 +22433,7 @@
 	}
 	GIV(newMethod) = methodArgument;
 	/* begin primitiveIndexOf: */
-	methodPointer = GIV(newMethod);
-	primBits = (((usqInt) (longAt((methodPointer + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primBits = (((usqInt) (longAt((GIV(newMethod) + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
 	primitiveIndex = (primBits & 511) + (((usqInt) primBits) >> 19);
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primitiveIndex > MaxPrimitiveIndex
@@ -22772,12 +22441,44 @@
 	: primitiveTable[primitiveIndex])));
 	GIV(argumentCount) = argCnt;
 	/* begin executeNewMethod */
+	VM_LABEL(1executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -22857,12 +22558,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 }
 
 
@@ -22925,7 +22620,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(27assertClassOfiscompactClassIndex);
+	VM_LABEL(26assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23016,7 +22711,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(28assertClassOfiscompactClassIndex);
+	VM_LABEL(27assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23415,7 +23110,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(29assertClassOfiscompactClassIndex);
+	VM_LABEL(28assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23477,7 +23172,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(30assertClassOfiscompactClassIndex);
+	VM_LABEL(29assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23558,12 +23253,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (1 * BytesPerWord));
 	index = longAt(GIV(stackPointer));
 	if (index == ConstOne) {
@@ -23611,12 +23300,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	oopToStore = longAt(GIV(stackPointer));
 	valueToStore = positive32BitValueOf(oopToStore);
 	if (!(GIV(primFailCode) == 0)) {
@@ -23676,7 +23359,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(31assertClassOfiscompactClassIndex);
+	VM_LABEL(30assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23738,7 +23421,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(32assertClassOfiscompactClassIndex);
+	VM_LABEL(31assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23829,7 +23512,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(33assertClassOfiscompactClassIndex);
+	VM_LABEL(32assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23891,7 +23574,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(34assertClassOfiscompactClassIndex);
+	VM_LABEL(33assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23976,7 +23659,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(35assertClassOfiscompactClassIndex);
+	VM_LABEL(34assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24038,7 +23721,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(36assertClassOfiscompactClassIndex);
+	VM_LABEL(35assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24123,7 +23806,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(37assertClassOfiscompactClassIndex);
+	VM_LABEL(36assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24185,7 +23868,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(38assertClassOfiscompactClassIndex);
+	VM_LABEL(37assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24270,7 +23953,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(39assertClassOfiscompactClassIndex);
+	VM_LABEL(38assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24332,7 +24015,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(40assertClassOfiscompactClassIndex);
+	VM_LABEL(39assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24417,7 +24100,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(41assertClassOfiscompactClassIndex);
+	VM_LABEL(40assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24479,7 +24162,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(42assertClassOfiscompactClassIndex);
+	VM_LABEL(41assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24568,7 +24251,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(43assertClassOfiscompactClassIndex);
+	VM_LABEL(42assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24630,7 +24313,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(44assertClassOfiscompactClassIndex);
+	VM_LABEL(43assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24713,7 +24396,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(45assertClassOfiscompactClassIndex);
+	VM_LABEL(44assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24775,7 +24458,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(46assertClassOfiscompactClassIndex);
+	VM_LABEL(45assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24864,7 +24547,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(47assertClassOfiscompactClassIndex);
+	VM_LABEL(46assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24926,7 +24609,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(48assertClassOfiscompactClassIndex);
+	VM_LABEL(47assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25026,6 +24709,8 @@
 DECL_MAYBE_SQ_GLOBAL_STRUCT
     sqInt i;
     sqInt oldMethod;
+    sqInt primBits;
+    sqInt primIdx;
     sqInt probe;
 
 	oldMethod = longAt(GIV(stackPointer));
@@ -25036,6 +24721,12 @@
 		}
 		probe += MethodCacheEntrySize;
 	}
+	/* begin primitiveIndexOf: */
+	primBits = (((usqInt) (longAt((oldMethod + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primIdx = (primBits & 511) + (((usqInt) primBits) >> 19);
+	if (primIdx == PrimitiveExternalCallIndex) {
+		flushExternalPrimitiveOf(oldMethod);
+	}
 }
 
 
@@ -25146,7 +24837,7 @@
 	/* begin floatValueOf: */
 	flag("Dan");
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(49assertClassOfiscompactClassIndex);
+	VM_LABEL(48assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25210,7 +24901,7 @@
 	/* begin floatValueOf: */
 	flag("Dan");
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(50assertClassOfiscompactClassIndex);
+	VM_LABEL(49assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (2 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25386,7 +25077,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(51assertClassOfiscompactClassIndex);
+	VM_LABEL(50assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -27773,7 +27464,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(52assertClassOfiscompactClassIndex);
+	VM_LABEL(51assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -29003,6 +28694,7 @@
 static sqInt
 primitiveObjectperformwithArgumentslookedUpIn(sqInt actualReceiver, sqInt selector, sqInt argumentArray, sqInt lookupClass) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt arraySize;
     sqInt delta;
     sqInt errorCode;
@@ -29010,6 +28702,7 @@
     sqInt i;
     sqInt index;
     sqInt methodHeader;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
@@ -29017,6 +28710,8 @@
     sqInt offset;
     sqInt performArgCount;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp11;
@@ -29086,12 +28781,44 @@
 	/* begin pop: */
 	GIV(stackPointer) += (performArgCount + 2) * BytesPerWord;
 	/* begin executeNewMethod */
+	VM_LABEL(2executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -29171,12 +28898,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	return null;
 }
 
@@ -29200,12 +28921,14 @@
 static void
 primitivePerform(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt ccIndex;
     sqInt errorCode;
     sqInt i;
     sqInt i1;
     sqInt lookupClass;
     sqInt methodHeader;
+    sqInt nArgs;
     sqInt newReceiver;
     sqInt numArgs;
     sqInt numTemps;
@@ -29213,6 +28936,8 @@
     sqInt performMethod;
     sqInt performSelector;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -29265,12 +28990,44 @@
 	}
 	if (GIV(primFailCode) == 0) {
 		/* begin executeNewMethod */
+		VM_LABEL(3executeNewMethod);
 		if (primitiveFunctionPointer != 0) {
 			if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 				externalQuickPrimitiveResponse();
 				goto l1;
 			}
-			slowPrimitiveResponse();
+			/* begin slowPrimitiveResponse */
+			if (FailImbalancedPrimitives) {
+				nArgs = GIV(argumentCount);
+				savedStackPointer = GIV(stackPointer);
+				savedFramePointer = GIV(framePointer);
+			}
+			/* begin initPrimCall */
+			GIV(primFailCode) = 0;
+			dispatchFunctionPointer(primitiveFunctionPointer);
+			if (FailImbalancedPrimitives
+			 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+					flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+					GIV(stackPointer) = savedStackPointer;
+					failUnbalancedPrimitive();
+				}
+			}
+			if (GIV(nextProfileTick) > 0) {
+				/* begin checkProfileTick: */
+				aPrimitiveMethod = GIV(newMethod);
+				assert(GIV(nextProfileTick) != 0);
+				if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+					GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+					GIV(profileMethod) = (GIV(primFailCode) == 0
+						? aPrimitiveMethod
+						: GIV(nilObj));
+					forceInterruptCheck();
+					GIV(nextProfileTick) = 0;
+				}
+			}
+			GIV(primFailCode) == 0;
 			if (GIV(primFailCode) == 0) {
 				goto l1;
 			}
@@ -29350,12 +29107,6 @@
 	l1:	/* end executeNewMethod */;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	else {
 		/* begin unPop: */
@@ -31152,7 +30903,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(53assertClassOfiscompactClassIndex);
+	VM_LABEL(52assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -31474,7 +31225,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(54assertClassOfiscompactClassIndex);
+	VM_LABEL(53assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -32939,7 +32690,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top2 = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(55assertClassOfiscompactClassIndex);
+	VM_LABEL(54assertClassOfiscompactClassIndex);
 	if ((top2 & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -33026,7 +32777,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(56assertClassOfiscompactClassIndex);
+	VM_LABEL(55assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -33540,36 +33291,18 @@
 		result = GIV(nilObj);
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 6) {
 		result = GIV(tenuringThreshold);
 		GIV(tenuringThreshold) = arg;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 23) {
 		result = extraVMMemory;
 		extraVMMemory = arg;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 24) {
 		result = GIV(shrinkThreshold);
@@ -33577,12 +33310,6 @@
 			GIV(shrinkThreshold) = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 25) {
@@ -33591,12 +33318,6 @@
 			GIV(growHeadroom) = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 26) {
@@ -33605,12 +33326,6 @@
 			ioSetHeartbeatMilliseconds(arg);
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 43) {
@@ -33620,12 +33335,6 @@
 			desiredNumStackPages = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 45) {
@@ -33634,12 +33343,6 @@
 			desiredEdenBytes = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if ((index == 47)
@@ -33649,12 +33352,6 @@
 			/* begin setDesiredCogCodeSize: */
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if ((index == 48)
@@ -33665,12 +33362,6 @@
 	: 4)) << 1) | 1);
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 			/* begin setCogVMFlags: */
 			if ((((usqInt)arg)) > 7) {
 				GIV(primFailCode) = PrimErrUnsupported;
@@ -33686,12 +33377,6 @@
 			result = ioGetMaxExtSemTableSize();
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 			/* begin setMaxExtSemSizeTo: */
 			GIV(maxExtSemTabSizeSet) = 1;
 			ioSetMaxExtSemTableSize(arg);
@@ -35370,21 +35055,7 @@
 	flush();
 }
 
-static void
-printUnbalancedStack(sqInt primIdx) {
-	print("Stack unbalanced after ");
-	if (GIV(primFailCode) == 0) {
-		print("successful primitive ");
-	}
-	else {
-		print("failed primitive ");
-	}
-	printNum(primIdx);
-	/* begin cr */
-	printf("\n");
-}
 
-
 /*	For testing in Smalltalk, this method should be overridden in a subclass. */
 
 void
@@ -35453,6 +35124,7 @@
 void
 pushRemappableOop(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 }
 
@@ -36005,12 +35677,6 @@
 	primFailCodeValue = GIV(primFailCode);
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	displayBitsOfLeftTopRightBottom(displayObj, 0, 0, (w >> 1), 1);
 	ioForceDisplayUpdate();
 	GIV(primFailCode) = primFailCodeValue;
@@ -36731,122 +36397,6 @@
 }
 
 
-/*	Called under the assumption that primFunctionPtr has been preloaded */
-
-static sqInt
-slowPrimitiveResponse(void) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt aPrimitiveMethod;
-    sqInt delta;
-    sqInt expectedPops;
-    sqInt nArgs;
-    char *savedFramePointer;
-    sqInt savedNewMethod;
-    char *savedStackPointer;
-    char *sp;
-
-	if (FailImbalancedPrimitives) {
-		nArgs = GIV(argumentCount);
-		savedStackPointer = GIV(stackPointer);
-		savedFramePointer = GIV(framePointer);
-	}
-	else {
-		if (DoBalanceChecks) {
-
-			/* check stack balance */
-
-			nArgs = GIV(argumentCount);
-
-			/* If frame pointer changes then primitive has sent or unwound.
-				  Stack will appear unbalanced in this case. */
-
-			delta = GIV(framePointer) - GIV(stackPointer);
-			savedFramePointer = GIV(framePointer);
-			savedNewMethod = GIV(newMethod);
-		}
-	}
-	/* begin initPrimCall */
-	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
-	dispatchFunctionPointer(primitiveFunctionPointer);
-	if (GIV(shouldPopArgs)) {
-		if (GIV(primFailCode) == 0) {
-
-			/* This was a plugin primitive. If the primitive was successful, pop the args,
-		push the return value. Otherwise leave things alone. */
-
-			expectedPops = GIV(argumentCount);
-			/* begin pop: */
-			GIV(stackPointer) += expectedPops * BytesPerWord;
-			if (!(GIV(primResult) == 0)) {
-				/* begin pop:thenPush: */
-				longAtput(sp = GIV(stackPointer) + ((1 - 1) * BytesPerWord), GIV(primResult));
-				GIV(stackPointer) = sp;
-			}
-		}
-		else {
-			expectedPops = 0;
-		}
-
-		/* clear result */
-		/* Verify that the primitive popped the expected number of args.
-		If we have zero primPops assume access via methodArg: etc. 
-		and don't complain. */
-
-		GIV(primResult) = 0;
-		if (!((GIV(primPops) == 0)
-			 || (expectedPops == GIV(primPops)))) {
-			fprintf(stderr,"[VM]: Warning: Primitive popped wrong number of args\n");
-			printCallStack();
-		}
-	}
-	if (FailImbalancedPrimitives) {
-		if ((GIV(primFailCode) == 0)
-		 && ((GIV(framePointer) == savedFramePointer)
- && (!0))) {
-			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-				/* Don't fail if primitive has done something radical, e.g. perform: */
-				/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-				/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-				GIV(stackPointer) = savedStackPointer;
-				failUnbalancedPrimitive();
-			}
-		}
-	}
-	else {
-		if (DoBalanceChecks
-		 && (GIV(framePointer) == savedFramePointer)) {
-			if (!((GIV(primFailCode) == 0
-					? (GIV(framePointer) - GIV(stackPointer)) == (delta - (nArgs * BytesPerWord))
-					: (GIV(framePointer) - GIV(stackPointer)) == delta))) {
-				printUnbalancedStack(primitiveIndexOf(savedNewMethod));
-			}
-		}
-	}
-	if (GIV(nextProfileTick) > 0) {
-		/* begin checkProfileTick: */
-		aPrimitiveMethod = GIV(newMethod);
-		assert(GIV(nextProfileTick) != 0);
-		if ((ioHighResClock()) >= GIV(nextProfileTick)) {
-			GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
-			GIV(profileMethod) = (GIV(primFailCode) == 0
-				? aPrimitiveMethod
-				: GIV(nilObj));
-			forceInterruptCheck();
-			GIV(nextProfileTick) = 0;
-		}
-	}
-	return GIV(primFailCode) == 0;
-}
-
-
 /*	update state of active context */
 
 static void
@@ -36886,6 +36436,7 @@
 	GIV(stackPointer) = sp2;
 	activeContext = voidVMStateForSnapshot();
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(activeContext));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = activeContext;
 	activeProc = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
 	/* begin storePointer:ofObject:withValue: */
@@ -37046,7 +36597,7 @@
 
 	floatPointer = longAt(GIV(stackPointer) + (offset * BytesPerWord));
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(57assertClassOfiscompactClassIndex);
+	VM_LABEL(56assertClassOfiscompactClassIndex);
 	if ((floatPointer & 1)) {
 		/* begin success: */
 		if (!(0)) {

Modified: branches/Cog/stacksrc/vm/interp.c
===================================================================
--- branches/Cog/stacksrc/vm/interp.c	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/stacksrc/vm/interp.c	2010-09-12 16:49:10 UTC (rev 2299)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
    from
-	StackInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
-static char __buildInfo[] = "StackInterpreter VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf " __DATE__ ;
+static char __buildInfo[] = "StackInterpreter VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -139,7 +139,6 @@
 #define CrossedX 258
 #define CtxtTempFrameStart 6
 #define DoAssertionChecks 0
-#define DoBalanceChecks 0
 #define DoExpensiveAssertionChecks 0
 #define Done 4
 #define DumpStackOnLowSpace 0
@@ -510,16 +509,6 @@
 static sqInt oopisGreaterThanandLessThan(sqInt anOop, sqInt baseOop, sqInt limitOop);
 static sqInt pageIndexFor(void *pointer);
 static sqInt pageListIsWellFormed(void);
-void pluginPop(sqInt nItems);
-void pluginPopthenPush(sqInt nItems, sqInt oop);
-void pluginPushBool(sqInt trueOrFalse);
-void pluginPushFloat(double  f);
-void pluginPushInteger(sqInt integerValue);
-void pluginPush(sqInt oop);
-double pluginStackFloatValue(sqInt index);
-sqInt pluginStackIntegerValue(sqInt index);
-sqInt pluginStackObjectValue(sqInt index);
-sqInt pluginStackValue(sqInt index);
 sqInt popRemappableOop(void);
 static sqInt popStack(void);
 sqInt pop(sqInt nItems);
@@ -781,7 +770,6 @@
 void printStackPagesInUse(void);
 static void printStackPage(StackPage *page);
 static void printStringOf(sqInt oop);
-static void printUnbalancedStack(sqInt primIdx);
 void print(char *s);
 void pushBool(sqInt trueOrFalse);
 static sqInt pushedReceiverOrClosureOfFrame(char *theFP);
@@ -829,7 +817,6 @@
 static sqInt sizeOfFree(sqInt oop);
 sqInt sizeOfSTArrayFromCPrimitive(void *cPtr);
 sqInt slotSizeOf(sqInt oop);
-static sqInt slowPrimitiveResponse(void);
 static void snapshot(sqInt embedded);
 static void space(void);
 sqInt splObj(sqInt index);
@@ -889,8 +876,8 @@
 _iss sqInt specialObjectsOop;
 _iss StackPage * stackPage;
 _iss char * framePointer;
-_iss usqInt method;
 _iss sqInt nilObj;
+_iss usqInt method;
 _iss usqInt freeStart;
 _iss sqInt argumentCount;
 _iss usqInt youngStart;
@@ -900,11 +887,8 @@
 _iss sqInt trueObj;
 _iss sqInt falseObj;
 _iss usqInt instructionPointer;
-_iss sqInt remapBufferCount;
 _iss usqInt newMethod;
-_iss sqInt primPops;
-_iss sqInt primResult;
-_iss sqInt shouldPopArgs;
+_iss sqInt remapBufferCount;
 _iss usqInt reserveStart;
 _iss StackPage * pages;
 _iss char * stackLimit;
@@ -912,23 +896,24 @@
 _iss char * stackMemory;
 _iss sqInt bytesPerPage;
 _iss usqInt memoryLimit;
+_iss sqLong nextProfileTick;
 _iss StackPage * mostRecentlyUsedPage;
 _iss sqInt needGCFlag;
 _iss usqInt scavengeThreshold;
 _iss usqInt fwdTableNext;
 _iss sqInt jmpDepth;
+_iss sqInt profileProcess;
 _iss sqInt numStackPages;
+_iss sqInt profileMethod;
 _iss usqInt compStart;
 _iss sqInt numPages;
 _iss sqInt growHeadroom;
-_iss sqInt profileProcess;
 _iss sqInt extraRootCount;
+_iss sqInt tempOop;
 _iss sqInt weakRootCount;
 _iss sqInt longRunningPrimitiveCheckSemaphore;
-_iss sqLong nextProfileTick;
 _iss usqLong nextWakeupUsecs;
 _iss sqInt preemptionYields;
-_iss sqInt profileMethod;
 _iss sqInt highestRunnableProcessPriority;
 _iss sqInt longRunningPrimitiveCheckMethod;
 _iss usqLong longRunningPrimitiveStartUsecs;
@@ -1004,7 +989,6 @@
 _iss sqInt weakRoots[WeakRootTableSize + 1 /* 2626 */];
 _iss jmp_buf jmpBuf[MaxJumpBuf + 1 /* 33 */];
 _iss unsigned long byteCount;
-_iss sqInt pageMap;
 #undef _iss
 #if SQ_USE_GLOBAL_STRUCT
  } fum;
@@ -1612,7 +1596,7 @@
  0 };
 char * breakSelector;
 sqInt breakSelectorLength = -1;
-const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.26]";
+const char *interpreterVersion = "Croquet Closure Stack VM [StackInterpreter VMMaker-oscog.27]";
 static volatile int sendTrace;
 sqInt suppressHeartbeatFlag;
 
@@ -1623,6 +1607,7 @@
 #define mostRecentlyUsedPage() GIV(mostRecentlyUsedPage)
 #define pageIndexForstackMemorybytesPerPage(pointer,stackmem,pageByteSize) (((char *)(pointer) - (stackmem) - 1) / (pageByteSize))
 #define printFloat(f) printf("%g", f)
+#define remapBufferCount() GIV(remapBufferCount)
 #define stackPageAtpages(index,pages) ((pages) + (index))
 
 
@@ -4313,6 +4298,9 @@
 				sqInt succeeded;
 				sqInt localPrimIndex;
 				sqInt oop;
+				sqInt nArgs;
+				char *savedFramePointer;
+				char *savedStackPointer;
 				sqInt errorCode;
 				sqInt i;
 				sqInt methodHeader;
@@ -4320,6 +4308,7 @@
 				sqInt rcvr;
 				sqInt table;
 				sqInt object;
+				sqInt aPrimitiveMethod;
 
 				VM_LABEL(0commonSend);
 								sendBreakpointreceiver(GIV(messageSelector) + BaseHeaderSize, lengthOf(GIV(messageSelector)), longAtPointer(localSP + (GIV(argumentCount) * BytesPerWord)));
@@ -4416,7 +4405,38 @@
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
 					GIV(framePointer) = localFP;
-					succeeded = slowPrimitiveResponse();
+					/* begin slowPrimitiveResponse */
+					if (FailImbalancedPrimitives) {
+						nArgs = GIV(argumentCount);
+						savedStackPointer = GIV(stackPointer);
+						savedFramePointer = GIV(framePointer);
+					}
+					/* begin initPrimCall */
+					GIV(primFailCode) = 0;
+					dispatchFunctionPointer(primitiveFunctionPointer);
+					if (FailImbalancedPrimitives
+					 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+						if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+							flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+							GIV(stackPointer) = savedStackPointer;
+							failUnbalancedPrimitive();
+						}
+					}
+					if (GIV(nextProfileTick) > 0) {
+						/* begin checkProfileTick: */
+						aPrimitiveMethod = GIV(newMethod);
+						assert(GIV(nextProfileTick) != 0);
+						if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+							GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+							GIV(profileMethod) = (GIV(primFailCode) == 0
+								? aPrimitiveMethod
+								: GIV(nilObj));
+							forceInterruptCheck();
+							GIV(nextProfileTick) = 0;
+						}
+					}
+					succeeded = GIV(primFailCode) == 0;
 					/* begin internalizeIPandSP */
 					localIP = pointerForOop(GIV(instructionPointer));
 					localSP = pointerForOop(GIV(stackPointer));
@@ -5330,12 +5350,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -5518,12 +5532,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -5752,12 +5760,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatLess:thanArg: */
 				VM_LABEL(0primitiveFloatLessthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6021,12 +6023,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatGreater:thanArg: */
 				VM_LABEL(0primitiveFloatGreaterthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6290,12 +6286,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatGreater:thanArg: */
 				VM_LABEL(1primitiveFloatGreaterthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6559,12 +6549,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatLess:thanArg: */
 				VM_LABEL(1primitiveFloatLessthanArg);
 				/* begin loadFloatOrIntFrom: */
@@ -6827,12 +6811,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatEqual:toArg: */
 				VM_LABEL(0primitiveFloatEqualtoArg);
 				/* begin loadFloatOrIntFrom: */
@@ -7095,12 +7073,6 @@
 				}
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin primitiveFloatEqual:toArg: */
 				VM_LABEL(1primitiveFloatEqualtoArg);
 				/* begin loadFloatOrIntFrom: */
@@ -7322,12 +7294,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -7518,12 +7484,6 @@
 				else {
 					/* begin initPrimCall */
 					GIV(primFailCode) = 0;
-					GIV(primPops) = 0;
-
-					/* mark as unused return value */
-
-					GIV(primResult) = 0;
-					GIV(shouldPopArgs) = 0;
 					/* begin externalizeIPandSP */
 					GIV(instructionPointer) = oopForPointer(localIP);
 					GIV(stackPointer) = localSP;
@@ -7693,12 +7653,6 @@
 				VM_LABEL(0bytecodePrimMod);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				mod = doPrimitiveModby(longAtPointer(localSP + (1 * BytesPerWord)), longAtPointer(localSP + (0 * BytesPerWord)));
 				if (GIV(primFailCode) == 0) {
 					/* begin internalPop:thenPush: */
@@ -7728,12 +7682,6 @@
 				VM_LABEL(0bytecodePrimMakePoint);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -7831,12 +7779,6 @@
 				VM_LABEL(0bytecodePrimBitShift);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -7937,12 +7879,6 @@
 				VM_LABEL(0bytecodePrimDiv);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				quotient = doPrimitiveDivby(longAtPointer(localSP + (1 * BytesPerWord)), longAtPointer(localSP + (0 * BytesPerWord)));
 				if (GIV(primFailCode) == 0) {
 					/* begin internalPop:thenPush: */
@@ -7973,12 +7909,6 @@
 				VM_LABEL(0bytecodePrimBitAnd);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -8037,12 +7967,6 @@
 				VM_LABEL(0bytecodePrimBitOr);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				/* begin externalizeIPandSP */
 				GIV(instructionPointer) = oopForPointer(localIP);
 				GIV(stackPointer) = localSP;
@@ -8263,13 +8187,7 @@
 				VM_LABEL(0bytecodePrimSize);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
 
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
-
 				/* Shortcut the mega-lookup for ByteString and Array, the two big consumers of cycles
 	 here. Both of these have compact class indices and neither has any added fields. */
 
@@ -8517,12 +8435,6 @@
 								block = longAtPointer(localSP);
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				GIV(argumentCount) = 0;
 				/* begin assertClassOf:is: */
 				if ((block & 1)) {
@@ -8589,12 +8501,6 @@
 								block = longAtPointer(localSP + (1 * BytesPerWord));
 				/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				GIV(argumentCount) = 1;
 				/* begin assertClassOf:is: */
 				if ((block & 1)) {
@@ -8693,12 +8599,6 @@
 				VM_LABEL(0bytecodePrimPointX);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				rcvr = longAtPointer(localSP);
 				/* begin assertClassOf:is: */
 				if ((rcvr & 1)) {
@@ -8756,12 +8656,6 @@
 				VM_LABEL(0bytecodePrimPointY);
 								/* begin initPrimCall */
 				GIV(primFailCode) = 0;
-				GIV(primPops) = 0;
-
-				/* mark as unused return value */
-
-				GIV(primResult) = 0;
-				GIV(shouldPopArgs) = 0;
 				rcvr = longAtPointer(localSP);
 				/* begin assertClassOf:is: */
 				if ((rcvr & 1)) {
@@ -9726,12 +9620,6 @@
 	GIV(jmpDepth) -= 1;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	return 1;
 }
 
@@ -10271,8 +10159,8 @@
 	if (!(checkOopIntegritynamed(GIV(profileSemaphore), "profileSemaphore"))) {
 		ok = 0;
 	}
-	if (!(GIV(primResult) == 0)) {
-		if (!(checkOopIntegritynamed(GIV(primResult), "primResult"))) {
+	if (!(GIV(tempOop) == 0)) {
+		if (!(checkOopIntegritynamed(GIV(tempOop), "tempOop"))) {
 			ok = 0;
 		}
 	}
@@ -10631,6 +10519,7 @@
 
 	bytes += extraHdrBytes;
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 	if (!(sufficientSpaceToAllocate(2500 + bytes))) {
 		return 0;
@@ -10704,12 +10593,6 @@
 	value = longAt(GIV(stackPointer));
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (2 * BytesPerWord));
 	if (!((rcvr & 1) == 0)) {
 		GIV(primFailCode) = PrimErrInappropriate; return;
@@ -10801,12 +10684,6 @@
 	}
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	if (stringy) {
 		stObjectatput(rcvr, index, asciiOfCharacter(value));
 	}
@@ -10843,12 +10720,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (1 * BytesPerWord));
 	if (!((rcvr & 1) == 0)) {
 		GIV(primFailCode) = PrimErrInappropriate; return;
@@ -10917,12 +10788,6 @@
 	}
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	result = stObjectat(rcvr, index);
 	if (GIV(primFailCode) == 0) {
 		if (stringy) {
@@ -14672,9 +14537,7 @@
 	GIV(profileMethod) = GIV(nilObj);
 	GIV(nextPollUsecs) = 0;
 	GIV(nextWakeupUsecs) = 0;
-	GIV(primPops) = 0;
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
+	GIV(tempOop) = 0;
 
 	/* cmd-. as used for Mac but no other OS */
 
@@ -15243,6 +15106,7 @@
 	if (newObj1 == 0) {
 		if (hdrSize > 1) {
 			/* begin pushRemappableOop: */
+			assert(addressCouldBeOop(header2));
 			GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = header2;
 		}
 		/* begin allocateChunkAfterGC: */
@@ -16325,8 +16189,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		GIV(longRunningPrimitiveCheckSemaphore) = remap(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		GIV(primResult) = remap(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		GIV(tempOop) = remap(GIV(tempOop));
 	}
 	for (i1 = 1; i1 <= GIV(remapBufferCount); i1 += 1) {
 		oop1 = GIV(remapBuffer)[i1];
@@ -16541,8 +16405,8 @@
 	if (GIV(longRunningPrimitiveCheckSemaphore) != null) {
 		markAndTrace(GIV(longRunningPrimitiveCheckSemaphore));
 	}
-	if (!(GIV(primResult) == 0)) {
-		markAndTrace(GIV(primResult));
+	if (!(GIV(tempOop) == 0)) {
+		markAndTrace(GIV(tempOop));
 	}
 	for (i = 1; i <= GIV(remapBufferCount); i += 1) {
 		oop = GIV(remapBuffer)[i];
@@ -17360,7 +17224,6 @@
 sqInt
 methodArg(sqInt index) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
 	if ((index > GIV(argumentCount)) + 1) {
 		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
 		printCallStack();
@@ -17391,17 +17254,17 @@
 }
 
 
-/*	Stores the return value from a primitive */
+/*	Sets the return value for a method. In the CoInterpreter we replace the
+	cumbersome primResult machinery. */
 
 sqInt
 methodReturnValue(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if (!(GIV(primResult) == 0)) {
-		fprintf(stderr, "[VM]: Attempt to set method return type multiple times\n");
-		printCallStack();
-	}
-	GIV(shouldPopArgs) = 1;
-	GIV(primResult) = oop;
+    char *sp;
+
+	/* begin pop:thenPush: */
+	longAtput(sp = GIV(stackPointer) + (((GIV(argumentCount) + 1) - 1) * BytesPerWord), oop);
+	GIV(stackPointer) = sp;
 	return 0;
 }
 
@@ -18088,278 +17951,6 @@
 }
 
 
-/*	The (obsolete) interface used by primitives that doesn't actually do
-	anything besides noting the fact someone tried to pop the given number of
-	elements 
- */
-
-void
-pluginPop(sqInt nItems) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
-	GIV(primPops) += nItems;
-}
-
-
-/*	A variant of pop:thenPush: used by primitives that doesn't actually do
-	anything besides noting the fact someone tried to pop the given number of
-	elements 
- */
-
-void
-pluginPopthenPush(sqInt nItems, sqInt oop) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	/* begin pluginPop: */
-	GIV(shouldPopArgs) = 1;
-	GIV(primPops) += nItems;
-	/* begin pluginPush: */
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushBool(sqInt trueOrFalse) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	if (trueOrFalse) {
-		/* begin pluginPush: */
-
-		/* a push counts as a negative pop */
-
-		GIV(primPops) -= 1;
-		methodReturnValue(GIV(trueObj));
-	}
-	else {
-		/* begin pluginPush: */
-
-		/* a push counts as a negative pop */
-
-		GIV(primPops) -= 1;
-		methodReturnValue(GIV(falseObj));
-	}
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushFloat(double  f) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt oop;
-
-	/* begin pluginPush: */
-	oop = floatObjectOf(f);
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only */
-
-void
-pluginPushInteger(sqInt integerValue) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	/* begin pluginPush: */
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(((integerValue << 1) | 1));
-}
-
-
-/*	A variant of push: used by primitives to communicate the return value */
-
-void
-pluginPush(sqInt oop) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-
-	/* a push counts as a negative pop */
-
-	GIV(primPops) -= 1;
-	methodReturnValue(oop);
-}
-
-
-/*	For plugin use only. */
-
-double
-pluginStackFloatValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt ccIndex;
-    sqInt floatPointer;
-    double result;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackFloatValue: */
-
-	/* N.B.  Because Slang always inlines assertClassOf:is:compactClassIndex:
-	 (because assertClassOf:is:compactClassIndex: has an inline: pragma) the
-	 phrase (self splObj: ClassArray) is expanded in-place and is _not_
-	 evaluated if ClassArrayCompactIndex is non-zero. */
-
-	floatPointer = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(23assertClassOfiscompactClassIndex);
-	if ((floatPointer & 1)) {
-		/* begin success: */
-		if (!(0)) {
-			if (GIV(primFailCode) == 0) {
-
-				/* Don't overwrite an error code that has already been set. */
-
-				GIV(primFailCode) = 1;
-			}
-		}
-		goto l1;
-	}
-	ccIndex = (((usqInt) (longAt(floatPointer))) >> 12) & 31;
-	if (ClassFloatCompactIndex == 0) {
-		if (ccIndex == 0) {
-			/* begin success: */
-			if (!(((longAt(floatPointer - BaseHeaderSize)) & AllButTypeMask) == (longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (ClassFloat << ShiftForWord))))) {
-				if (GIV(primFailCode) == 0) {
-
-					/* Don't overwrite an error code that has already been set. */
-
-					GIV(primFailCode) = 1;
-				}
-			}
-		}
-		else {
-			/* begin success: */
-			if (!(0)) {
-				if (GIV(primFailCode) == 0) {
-
-					/* Don't overwrite an error code that has already been set. */
-
-					GIV(primFailCode) = 1;
-				}
-			}
-		}
-	}
-	else {
-		/* begin success: */
-		if (!(ClassFloatCompactIndex == ccIndex)) {
-			if (GIV(primFailCode) == 0) {
-
-				/* Don't overwrite an error code that has already been set. */
-
-				GIV(primFailCode) = 1;
-			}
-		}
-	}
-l1:	/* end assertClassOf:is:compactClassIndex: */;
-	if (GIV(primFailCode) == 0) {
-		;
-		fetchFloatAtinto(floatPointer + BaseHeaderSize, result);
-		return result;
-	}
-	else {
-		return 0.0;
-	}
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackIntegerValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt integerPointer;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackIntegerValue: */
-	integerPointer = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	/* begin checkedIntegerValueOf: */
-	if ((integerPointer & 1)) {
-		return (integerPointer >> 1);
-	}
-	else {
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackObjectValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt oop;
-
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	/* begin stackObjectValue: */
-	oop = longAt(GIV(stackPointer) + (index * BytesPerWord));
-	if ((oop & 1)) {
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return null;
-	}
-	return oop;
-}
-
-
-/*	For plugin use only. */
-
-sqInt
-pluginStackValue(sqInt index) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-	GIV(shouldPopArgs) = 1;
-	if (index > (GIV(argumentCount) + 1)) {
-		fprintf(stderr,"[VM]: Attempt to access method args beyond range\n");
-		printCallStack();
-		/* begin primitiveFail */
-		if (GIV(primFailCode) == 0) {
-			GIV(primFailCode) = 1;
-		}
-		return 0;
-	}
-	return longAt(GIV(stackPointer) + (index * BytesPerWord));
-}
-
-
 /*	Pop and return the possibly remapped object from the remap buffer. */
 
 sqInt
@@ -18464,7 +18055,7 @@
 		return value;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(24assertClassOfiscompactClassIndex);
+	VM_LABEL(23assertClassOfiscompactClassIndex);
 	if ((oop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -19087,7 +18678,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(25assertClassOfiscompactClassIndex);
+	VM_LABEL(24assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -20294,6 +19885,7 @@
 		return;
 	}
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(result));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = result;
 	longAtput(((GIV(remapBuffer)[GIV(remapBufferCount)]) + BaseHeaderSize) + (0 << ShiftForWord), ((runInNOut << 1) | 1));
 	v1 = positive32BitIntegerFor(usecs);
@@ -22107,7 +21699,7 @@
 		GIV(primFailCode) = -3; return;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(26assertClassOfiscompactClassIndex);
+	VM_LABEL(25assertClassOfiscompactClassIndex);
 	oop9 = spec = longAt((methodArg + BaseHeaderSize) + (1 << ShiftForWord));
 	if ((oop9 & 1)) {
 		/* begin success: */
@@ -22251,21 +21843,25 @@
 	}
 	/* begin pushRemappableOop: */
 	oop1 = argumentArray = popStack();
+	assert(addressCouldBeOop(oop1));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop1;
 	/* begin pushRemappableOop: */
 	oop2 = primRcvr = popStack();
+	assert(addressCouldBeOop(oop2));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop2;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop3 = top;
+	assert(addressCouldBeOop(oop3));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop3;
 	/* begin pushRemappableOop: */
 	/* begin popStack */
 	top1 = longAt(GIV(stackPointer));
 	GIV(stackPointer) += BytesPerWord;
 	oop4 = top1;
+	assert(addressCouldBeOop(oop4));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop4;
 	/* begin push: */
 	longAtput(sp5 = GIV(stackPointer) - BytesPerWord, primRcvr);
@@ -22324,14 +21920,17 @@
 static void
 primitiveDoPrimitiveWithArgs(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt argumentArray;
     sqInt arraySize;
     sqInt cntxSize;
     sqInt header;
     sqInt index;
     sqInt integerPointer;
-    sqInt oop;
+    sqInt nArgs;
     sqInt primIdx;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22393,12 +21992,19 @@
 		}
 		return;
 	}
-	/* begin pop: */
-	GIV(stackPointer) += 2 * BytesPerWord;
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primIdx > MaxPrimitiveIndex
 	? 0
 	: primitiveTable[primIdx])));
+	if (primitiveFunctionPointer == 0) {
+		/* begin primitiveFail */
+		if (GIV(primFailCode) == 0) {
+			GIV(primFailCode) = 1;
+		}
+		return;
+	}
+	/* begin pop: */
+	GIV(stackPointer) += 2 * BytesPerWord;
 	GIV(argumentCount) = arraySize;
 	index = 1;
 	while (index <= GIV(argumentCount)) {
@@ -22411,14 +22017,46 @@
 		externalQuickPrimitiveResponse();
 		return;
 	}
-	/* begin pushRemappableOop: */
-	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = argumentArray;
+
+	/* prim might alloc/gc */
+
+	GIV(tempOop) = argumentArray;
+
+	/* Run the primitive (sets primFailCode) */
+
 	GIV(lkupClass) = GIV(nilObj);
-	slowPrimitiveResponse();
-	/* begin popRemappableOop */
-	oop = GIV(remapBuffer)[GIV(remapBufferCount)];
-	GIV(remapBufferCount) -= 1;
-	argumentArray = oop;
+	/* begin slowPrimitiveResponse */
+	if (FailImbalancedPrimitives) {
+		nArgs = GIV(argumentCount);
+		savedStackPointer = GIV(stackPointer);
+		savedFramePointer = GIV(framePointer);
+	}
+	/* begin initPrimCall */
+	GIV(primFailCode) = 0;
+	dispatchFunctionPointer(primitiveFunctionPointer);
+	if (FailImbalancedPrimitives
+	 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+		if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+			flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+			GIV(stackPointer) = savedStackPointer;
+			failUnbalancedPrimitive();
+		}
+	}
+	if (GIV(nextProfileTick) > 0) {
+		/* begin checkProfileTick: */
+		aPrimitiveMethod = GIV(newMethod);
+		assert(GIV(nextProfileTick) != 0);
+		if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+			GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+			GIV(profileMethod) = (GIV(primFailCode) == 0
+				? aPrimitiveMethod
+				: GIV(nilObj));
+			forceInterruptCheck();
+			GIV(nextProfileTick) = 0;
+		}
+	}
+	GIV(primFailCode) == 0;
 	if (!(GIV(primFailCode) == 0)) {
 		/* begin pop: */
 		GIV(stackPointer) += arraySize * BytesPerWord;
@@ -22427,10 +22065,11 @@
 		longAtput(sp2 = GIV(stackPointer) - BytesPerWord, ((primIdx << 1) | 1));
 		GIV(stackPointer) = sp2;
 		/* begin push: */
-		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, argumentArray);
+		longAtput(sp1 = GIV(stackPointer) - BytesPerWord, GIV(tempOop));
 		GIV(stackPointer) = sp1;
 		GIV(argumentCount) = 2;
 	}
+	GIV(tempOop) = 0;
 }
 
 
@@ -22568,17 +22207,20 @@
 static void
 primitiveExecuteMethod(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt errorCode;
     sqInt i;
     sqInt methodArgument;
     sqInt methodHeader;
-    sqInt methodPointer;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
     sqInt primBits;
     sqInt primitiveIndex;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22602,8 +22244,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	GIV(newMethod) = ((sqInt) top);
 	/* begin primitiveIndexOf: */
-	methodPointer = GIV(newMethod);
-	primBits = (((usqInt) (longAt((methodPointer + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primBits = (((usqInt) (longAt((GIV(newMethod) + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
 	primitiveIndex = (primBits & 511) + (((usqInt) primBits) >> 19);
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primitiveIndex > MaxPrimitiveIndex
@@ -22611,12 +22252,44 @@
 	: primitiveTable[primitiveIndex])));
 	GIV(argumentCount) -= 1;
 	/* begin executeNewMethod */
+	VM_LABEL(0executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -22696,12 +22369,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 }
 
 
@@ -22714,6 +22381,7 @@
 static void
 primitiveExecuteMethodArgsArray(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt argCnt;
     sqInt argumentArray;
     sqInt errorCode;
@@ -22721,13 +22389,15 @@
     sqInt i1;
     sqInt methodArgument;
     sqInt methodHeader;
-    sqInt methodPointer;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
     sqInt primBits;
     sqInt primitiveIndex;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -22759,8 +22429,7 @@
 	}
 	GIV(newMethod) = methodArgument;
 	/* begin primitiveIndexOf: */
-	methodPointer = GIV(newMethod);
-	primBits = (((usqInt) (longAt((methodPointer + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primBits = (((usqInt) (longAt((GIV(newMethod) + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
 	primitiveIndex = (primBits & 511) + (((usqInt) primBits) >> 19);
 	/* begin functionPointerFor:inClass: */
 	primitiveFunctionPointer = ((void (*)(void)) ((primitiveIndex > MaxPrimitiveIndex
@@ -22768,12 +22437,44 @@
 	: primitiveTable[primitiveIndex])));
 	GIV(argumentCount) = argCnt;
 	/* begin executeNewMethod */
+	VM_LABEL(1executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -22853,12 +22554,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 }
 
 
@@ -22921,7 +22616,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(27assertClassOfiscompactClassIndex);
+	VM_LABEL(26assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23012,7 +22707,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(28assertClassOfiscompactClassIndex);
+	VM_LABEL(27assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23411,7 +23106,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(29assertClassOfiscompactClassIndex);
+	VM_LABEL(28assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23473,7 +23168,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(30assertClassOfiscompactClassIndex);
+	VM_LABEL(29assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23554,12 +23249,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	rcvr = longAt(GIV(stackPointer) + (1 * BytesPerWord));
 	index = longAt(GIV(stackPointer));
 	if (index == ConstOne) {
@@ -23607,12 +23296,6 @@
 
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	oopToStore = longAt(GIV(stackPointer));
 	valueToStore = positive32BitValueOf(oopToStore);
 	if (!(GIV(primFailCode) == 0)) {
@@ -23672,7 +23355,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(31assertClassOfiscompactClassIndex);
+	VM_LABEL(30assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23734,7 +23417,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(32assertClassOfiscompactClassIndex);
+	VM_LABEL(31assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23825,7 +23508,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(33assertClassOfiscompactClassIndex);
+	VM_LABEL(32assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23887,7 +23570,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(34assertClassOfiscompactClassIndex);
+	VM_LABEL(33assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -23972,7 +23655,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(35assertClassOfiscompactClassIndex);
+	VM_LABEL(34assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24034,7 +23717,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(36assertClassOfiscompactClassIndex);
+	VM_LABEL(35assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24119,7 +23802,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(37assertClassOfiscompactClassIndex);
+	VM_LABEL(36assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24181,7 +23864,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(38assertClassOfiscompactClassIndex);
+	VM_LABEL(37assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24266,7 +23949,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(39assertClassOfiscompactClassIndex);
+	VM_LABEL(38assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24328,7 +24011,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(40assertClassOfiscompactClassIndex);
+	VM_LABEL(39assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24413,7 +24096,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(41assertClassOfiscompactClassIndex);
+	VM_LABEL(40assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24475,7 +24158,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(42assertClassOfiscompactClassIndex);
+	VM_LABEL(41assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24564,7 +24247,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(43assertClassOfiscompactClassIndex);
+	VM_LABEL(42assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24626,7 +24309,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(44assertClassOfiscompactClassIndex);
+	VM_LABEL(43assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24709,7 +24392,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(45assertClassOfiscompactClassIndex);
+	VM_LABEL(44assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24771,7 +24454,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(46assertClassOfiscompactClassIndex);
+	VM_LABEL(45assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24860,7 +24543,7 @@
 		goto l1;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(47assertClassOfiscompactClassIndex);
+	VM_LABEL(46assertClassOfiscompactClassIndex);
 	if ((rcvrOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -24922,7 +24605,7 @@
 		goto l2;
 	}
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(48assertClassOfiscompactClassIndex);
+	VM_LABEL(47assertClassOfiscompactClassIndex);
 	if ((argOop & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25022,6 +24705,8 @@
 DECL_MAYBE_SQ_GLOBAL_STRUCT
     sqInt i;
     sqInt oldMethod;
+    sqInt primBits;
+    sqInt primIdx;
     sqInt probe;
 
 	oldMethod = longAt(GIV(stackPointer));
@@ -25032,6 +24717,12 @@
 		}
 		probe += MethodCacheEntrySize;
 	}
+	/* begin primitiveIndexOf: */
+	primBits = (((usqInt) (longAt((oldMethod + BaseHeaderSize) + (HeaderIndex << ShiftForWord)))) >> 1) & 268435967;
+	primIdx = (primBits & 511) + (((usqInt) primBits) >> 19);
+	if (primIdx == PrimitiveExternalCallIndex) {
+		flushExternalPrimitiveOf(oldMethod);
+	}
 }
 
 
@@ -25142,7 +24833,7 @@
 	/* begin floatValueOf: */
 	flag("Dan");
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(49assertClassOfiscompactClassIndex);
+	VM_LABEL(48assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (1 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25206,7 +24897,7 @@
 	/* begin floatValueOf: */
 	flag("Dan");
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(50assertClassOfiscompactClassIndex);
+	VM_LABEL(49assertClassOfiscompactClassIndex);
 	if (((longAt(GIV(stackPointer) + (2 * BytesPerWord))) & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -25382,7 +25073,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(51assertClassOfiscompactClassIndex);
+	VM_LABEL(50assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -27769,7 +27460,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(52assertClassOfiscompactClassIndex);
+	VM_LABEL(51assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -28999,6 +28690,7 @@
 static sqInt
 primitiveObjectperformwithArgumentslookedUpIn(sqInt actualReceiver, sqInt selector, sqInt argumentArray, sqInt lookupClass) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt arraySize;
     sqInt delta;
     sqInt errorCode;
@@ -29006,6 +28698,7 @@
     sqInt i;
     sqInt index;
     sqInt methodHeader;
+    sqInt nArgs;
     sqInt numArgs;
     sqInt numTemps;
     sqInt object;
@@ -29013,6 +28706,8 @@
     sqInt offset;
     sqInt performArgCount;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp11;
@@ -29082,12 +28777,44 @@
 	/* begin pop: */
 	GIV(stackPointer) += (performArgCount + 2) * BytesPerWord;
 	/* begin executeNewMethod */
+	VM_LABEL(2executeNewMethod);
 	if (primitiveFunctionPointer != 0) {
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
 			goto l1;
 		}
-		slowPrimitiveResponse();
+		/* begin slowPrimitiveResponse */
+		if (FailImbalancedPrimitives) {
+			nArgs = GIV(argumentCount);
+			savedStackPointer = GIV(stackPointer);
+			savedFramePointer = GIV(framePointer);
+		}
+		/* begin initPrimCall */
+		GIV(primFailCode) = 0;
+		dispatchFunctionPointer(primitiveFunctionPointer);
+		if (FailImbalancedPrimitives
+		 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+				flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+				GIV(stackPointer) = savedStackPointer;
+				failUnbalancedPrimitive();
+			}
+		}
+		if (GIV(nextProfileTick) > 0) {
+			/* begin checkProfileTick: */
+			aPrimitiveMethod = GIV(newMethod);
+			assert(GIV(nextProfileTick) != 0);
+			if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+				GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+				GIV(profileMethod) = (GIV(primFailCode) == 0
+					? aPrimitiveMethod
+					: GIV(nilObj));
+				forceInterruptCheck();
+				GIV(nextProfileTick) = 0;
+			}
+		}
+		GIV(primFailCode) == 0;
 		if (GIV(primFailCode) == 0) {
 			goto l1;
 		}
@@ -29167,12 +28894,6 @@
 l1:	/* end executeNewMethod */;
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	return null;
 }
 
@@ -29196,12 +28917,14 @@
 static void
 primitivePerform(void) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+    sqInt aPrimitiveMethod;
     sqInt ccIndex;
     sqInt errorCode;
     sqInt i;
     sqInt i1;
     sqInt lookupClass;
     sqInt methodHeader;
+    sqInt nArgs;
     sqInt newReceiver;
     sqInt numArgs;
     sqInt numTemps;
@@ -29209,6 +28932,8 @@
     sqInt performMethod;
     sqInt performSelector;
     sqInt rcvr;
+    char *savedFramePointer;
+    char *savedStackPointer;
     char *sp;
     char *sp1;
     char *sp2;
@@ -29261,12 +28986,44 @@
 	}
 	if (GIV(primFailCode) == 0) {
 		/* begin executeNewMethod */
+		VM_LABEL(3executeNewMethod);
 		if (primitiveFunctionPointer != 0) {
 			if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 				externalQuickPrimitiveResponse();
 				goto l1;
 			}
-			slowPrimitiveResponse();
+			/* begin slowPrimitiveResponse */
+			if (FailImbalancedPrimitives) {
+				nArgs = GIV(argumentCount);
+				savedStackPointer = GIV(stackPointer);
+				savedFramePointer = GIV(framePointer);
+			}
+			/* begin initPrimCall */
+			GIV(primFailCode) = 0;
+			dispatchFunctionPointer(primitiveFunctionPointer);
+			if (FailImbalancedPrimitives
+			 && ((GIV(primFailCode) == 0)
+ && (GIV(framePointer) == savedFramePointer))) {
+				if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
+					flag("Would be nice to make this a message send of e.g. unbalancedPrimitive to the current process or context");
+					GIV(stackPointer) = savedStackPointer;
+					failUnbalancedPrimitive();
+				}
+			}
+			if (GIV(nextProfileTick) > 0) {
+				/* begin checkProfileTick: */
+				aPrimitiveMethod = GIV(newMethod);
+				assert(GIV(nextProfileTick) != 0);
+				if ((ioHighResClock()) >= GIV(nextProfileTick)) {
+					GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
+					GIV(profileMethod) = (GIV(primFailCode) == 0
+						? aPrimitiveMethod
+						: GIV(nilObj));
+					forceInterruptCheck();
+					GIV(nextProfileTick) = 0;
+				}
+			}
+			GIV(primFailCode) == 0;
 			if (GIV(primFailCode) == 0) {
 				goto l1;
 			}
@@ -29346,12 +29103,6 @@
 	l1:	/* end executeNewMethod */;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	else {
 		/* begin unPop: */
@@ -31148,7 +30899,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(53assertClassOfiscompactClassIndex);
+	VM_LABEL(52assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -31470,7 +31221,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(54assertClassOfiscompactClassIndex);
+	VM_LABEL(53assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -32935,7 +32686,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top2 = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(55assertClassOfiscompactClassIndex);
+	VM_LABEL(54assertClassOfiscompactClassIndex);
 	if ((top2 & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -33022,7 +32773,7 @@
 	GIV(stackPointer) += BytesPerWord;
 	top = top1;
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(56assertClassOfiscompactClassIndex);
+	VM_LABEL(55assertClassOfiscompactClassIndex);
 	if ((top & 1)) {
 		/* begin success: */
 		if (!(0)) {
@@ -33536,36 +33287,18 @@
 		result = GIV(nilObj);
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 6) {
 		result = GIV(tenuringThreshold);
 		GIV(tenuringThreshold) = arg;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 23) {
 		result = extraVMMemory;
 		extraVMMemory = arg;
 		/* begin initPrimCall */
 		GIV(primFailCode) = 0;
-		GIV(primPops) = 0;
-
-		/* mark as unused return value */
-
-		GIV(primResult) = 0;
-		GIV(shouldPopArgs) = 0;
 	}
 	if (index == 24) {
 		result = GIV(shrinkThreshold);
@@ -33573,12 +33306,6 @@
 			GIV(shrinkThreshold) = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 25) {
@@ -33587,12 +33314,6 @@
 			GIV(growHeadroom) = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 26) {
@@ -33601,12 +33322,6 @@
 			ioSetHeartbeatMilliseconds(arg);
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 43) {
@@ -33616,12 +33331,6 @@
 			desiredNumStackPages = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if (index == 45) {
@@ -33630,12 +33339,6 @@
 			desiredEdenBytes = arg;
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if ((index == 47)
@@ -33645,12 +33348,6 @@
 			/* begin setDesiredCogCodeSize: */
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 		}
 	}
 	if ((index == 48)
@@ -33661,12 +33358,6 @@
 	: 4)) << 1) | 1);
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 			/* begin setCogVMFlags: */
 			if ((((usqInt)arg)) > 7) {
 				GIV(primFailCode) = PrimErrUnsupported;
@@ -33682,12 +33373,6 @@
 			result = ioGetMaxExtSemTableSize();
 			/* begin initPrimCall */
 			GIV(primFailCode) = 0;
-			GIV(primPops) = 0;
-
-			/* mark as unused return value */
-
-			GIV(primResult) = 0;
-			GIV(shouldPopArgs) = 0;
 			/* begin setMaxExtSemSizeTo: */
 			GIV(maxExtSemTabSizeSet) = 1;
 			ioSetMaxExtSemTableSize(arg);
@@ -35366,21 +35051,7 @@
 	flush();
 }
 
-static void
-printUnbalancedStack(sqInt primIdx) {
-	print("Stack unbalanced after ");
-	if (GIV(primFailCode) == 0) {
-		print("successful primitive ");
-	}
-	else {
-		print("failed primitive ");
-	}
-	printNum(primIdx);
-	/* begin cr */
-	printf("\n");
-}
 
-
 /*	For testing in Smalltalk, this method should be overridden in a subclass. */
 
 void
@@ -35449,6 +35120,7 @@
 void
 pushRemappableOop(sqInt oop) {
 DECL_MAYBE_SQ_GLOBAL_STRUCT
+	assert(addressCouldBeOop(oop));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = oop;
 }
 
@@ -36001,12 +35673,6 @@
 	primFailCodeValue = GIV(primFailCode);
 	/* begin initPrimCall */
 	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
 	displayBitsOfLeftTopRightBottom(displayObj, 0, 0, (w >> 1), 1);
 	ioForceDisplayUpdate();
 	GIV(primFailCode) = primFailCodeValue;
@@ -36727,122 +36393,6 @@
 }
 
 
-/*	Called under the assumption that primFunctionPtr has been preloaded */
-
-static sqInt
-slowPrimitiveResponse(void) {
-DECL_MAYBE_SQ_GLOBAL_STRUCT
-    sqInt aPrimitiveMethod;
-    sqInt delta;
-    sqInt expectedPops;
-    sqInt nArgs;
-    char *savedFramePointer;
-    sqInt savedNewMethod;
-    char *savedStackPointer;
-    char *sp;
-
-	if (FailImbalancedPrimitives) {
-		nArgs = GIV(argumentCount);
-		savedStackPointer = GIV(stackPointer);
-		savedFramePointer = GIV(framePointer);
-	}
-	else {
-		if (DoBalanceChecks) {
-
-			/* check stack balance */
-
-			nArgs = GIV(argumentCount);
-
-			/* If frame pointer changes then primitive has sent or unwound.
-				  Stack will appear unbalanced in this case. */
-
-			delta = GIV(framePointer) - GIV(stackPointer);
-			savedFramePointer = GIV(framePointer);
-			savedNewMethod = GIV(newMethod);
-		}
-	}
-	/* begin initPrimCall */
-	GIV(primFailCode) = 0;
-	GIV(primPops) = 0;
-
-	/* mark as unused return value */
-
-	GIV(primResult) = 0;
-	GIV(shouldPopArgs) = 0;
-	dispatchFunctionPointer(primitiveFunctionPointer);
-	if (GIV(shouldPopArgs)) {
-		if (GIV(primFailCode) == 0) {
-
-			/* This was a plugin primitive. If the primitive was successful, pop the args,
-		push the return value. Otherwise leave things alone. */
-
-			expectedPops = GIV(argumentCount);
-			/* begin pop: */
-			GIV(stackPointer) += expectedPops * BytesPerWord;
-			if (!(GIV(primResult) == 0)) {
-				/* begin pop:thenPush: */
-				longAtput(sp = GIV(stackPointer) + ((1 - 1) * BytesPerWord), GIV(primResult));
-				GIV(stackPointer) = sp;
-			}
-		}
-		else {
-			expectedPops = 0;
-		}
-
-		/* clear result */
-		/* Verify that the primitive popped the expected number of args.
-		If we have zero primPops assume access via methodArg: etc. 
-		and don't complain. */
-
-		GIV(primResult) = 0;
-		if (!((GIV(primPops) == 0)
-			 || (expectedPops == GIV(primPops)))) {
-			fprintf(stderr,"[VM]: Warning: Primitive popped wrong number of args\n");
-			printCallStack();
-		}
-	}
-	if (FailImbalancedPrimitives) {
-		if ((GIV(primFailCode) == 0)
-		 && ((GIV(framePointer) == savedFramePointer)
- && (!0))) {
-			if (GIV(stackPointer) != (savedStackPointer + (nArgs * BytesPerWord))) {
-
-				/* Don't fail if primitive has done something radical, e.g. perform: */
-				/* Soon make this a message send of e.g. unbalancedPrimitive to the current process or context */
-				/* This is necessary but insufficient; the result may still have been written to the stack. */
-
-				GIV(stackPointer) = savedStackPointer;
-				failUnbalancedPrimitive();
-			}
-		}
-	}
-	else {
-		if (DoBalanceChecks
-		 && (GIV(framePointer) == savedFramePointer)) {
-			if (!((GIV(primFailCode) == 0
-					? (GIV(framePointer) - GIV(stackPointer)) == (delta - (nArgs * BytesPerWord))
-					: (GIV(framePointer) - GIV(stackPointer)) == delta))) {
-				printUnbalancedStack(primitiveIndexOf(savedNewMethod));
-			}
-		}
-	}
-	if (GIV(nextProfileTick) > 0) {
-		/* begin checkProfileTick: */
-		aPrimitiveMethod = GIV(newMethod);
-		assert(GIV(nextProfileTick) != 0);
-		if ((ioHighResClock()) >= GIV(nextProfileTick)) {
-			GIV(profileProcess) = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
-			GIV(profileMethod) = (GIV(primFailCode) == 0
-				? aPrimitiveMethod
-				: GIV(nilObj));
-			forceInterruptCheck();
-			GIV(nextProfileTick) = 0;
-		}
-	}
-	return GIV(primFailCode) == 0;
-}
-
-
 /*	update state of active context */
 
 static void
@@ -36882,6 +36432,7 @@
 	GIV(stackPointer) = sp2;
 	activeContext = voidVMStateForSnapshot();
 	/* begin pushRemappableOop: */
+	assert(addressCouldBeOop(activeContext));
 	GIV(remapBuffer)[(GIV(remapBufferCount) += 1)] = activeContext;
 	activeProc = longAt(((longAt(((longAt((GIV(specialObjectsOop) + BaseHeaderSize) + (SchedulerAssociation << ShiftForWord))) + BaseHeaderSize) + (ValueIndex << ShiftForWord))) + BaseHeaderSize) + (ActiveProcessIndex << ShiftForWord));
 	/* begin storePointer:ofObject:withValue: */
@@ -37042,7 +36593,7 @@
 
 	floatPointer = longAt(GIV(stackPointer) + (offset * BytesPerWord));
 	/* begin assertClassOf:is:compactClassIndex: */
-	VM_LABEL(57assertClassOfiscompactClassIndex);
+	VM_LABEL(56assertClassOfiscompactClassIndex);
 	if ((floatPointer & 1)) {
 		/* begin success: */
 		if (!(0)) {

Modified: branches/Cog/stacksrc/vm/interp.h
===================================================================
--- branches/Cog/stacksrc/vm/interp.h	2010-09-11 22:23:16 UTC (rev 2298)
+++ branches/Cog/stacksrc/vm/interp.h	2010-09-12 16:49:10 UTC (rev 2299)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.26 uuid: 8f0241dd-f8f9-4ae4-a736-bb81484acebf
+	CCodeGeneratorGlobalStructure VMMaker-oscog.27 uuid: 7bc4e8e8-b779-4140-8698-5cde0d003c0f
  */
 
 #define STACKVM 1



More information about the Vm-dev mailing list