[Vm-dev] [commit] r2337 - OSCogVM SimpleStackBasedCogit as per VMMaker-oscog.41.

commits at squeakvm.org commits at squeakvm.org
Sat Jan 1 20:18:50 UTC 2011


Author: eliot
Date: 2011-01-01 12:18:49 -0800 (Sat, 01 Jan 2011)
New Revision: 2337

Modified:
   branches/Cog/cygwinbuild/HowToBuild
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/image/Workspace.text
   branches/Cog/src/vm/cogit.c
   branches/Cog/src/vm/cogit.h
   branches/Cog/src/vm/cointerp.c
   branches/Cog/src/vm/gcc3x-cointerp.c
Log:
OSCogVM SimpleStackBasedCogit as per VMMaker-oscog.41.
Fix a bug with bytecode to pc mapping being confused by frameless
blocks which caused a crash when converting an interpreter
activation of Cogit class>>generatorTableFrom: to machine code.

Fix SimpleStackBasedCogit compilation by ifdeffing out the body of
enterRegisterArgCogMethod:at:receiver: and addding dummy
registerMaskFor:... defs.

Fix an assert for objects-as-methods in activateInterpreterMethod...


Modified: branches/Cog/cygwinbuild/HowToBuild
===================================================================
--- branches/Cog/cygwinbuild/HowToBuild	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/cygwinbuild/HowToBuild	2011-01-01 20:18:49 UTC (rev 2337)
@@ -31,7 +31,10 @@
    cygwinbuild/build/vm folder (make sure you copy Croquet.map along with it)
 
 3a. The cygwin makefile supports building three VM configurations, product,
-    assert and debug, building product by default.  The configurations are
+    assert and debug, building product by default.  To build a configuration
+	simply type make configuration, e.g.
+		make assert
+	The configurations are
 	product: stripped  & unstripped production VMs optimized at -O2 in
 		build/vm/Croquet.exe
 		build/vm/CroquetUnstripped.exe

Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes	2011-01-01 20:18:49 UTC (rev 2337)
@@ -150426,4 +150426,1134 @@
 		platformDir: (FileDirectory default / '../platforms') fullName
 		excluding:#(BrokenPlugin SlangTestPlugin TestOSAPlugin
 					FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin
-					NewsqueakIA32ABIPlugin NewsqueakIA32ABIPluginAttic)!
\ No newline at end of file
+					NewsqueakIA32ABIPlugin NewsqueakIA32ABIPluginAttic)!
+
+----STARTUP----{31 December 2010 . 6:42:49 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 31 December 2010 at 12:58:22 pm'!
+!CoInterpreter methodsFor: 'trampolines' stamp: 'eem 12/31/2010 11:46' prior: 34481786!
+activateInterpreterMethodFromMachineCode
+	"Execute an interpreted method from machine code.  We assume (require) that newMethod
+	 messageSelector, primitiveFunctionPointer and argumentCount have been set in the caller.
+	 Once evaluated either continue in the interpreter via a jongjmp or in machine code via an
+	 enilopmart (a form of longjmp - a stinking rose by any other name)."
+	<inline: false>
+	cogit assertCStackWellAligned.
+	self assert: (self validInstructionPointer: self stackTop inFrame: framePointer).
+	instructionPointer := self popStack.
+	primitiveFunctionPointer ~= 0
+		ifTrue:
+			[primitiveFunctionPointer = #primitiveInvokeObjectAsMethod asSymbol
+				ifTrue: [self assert: (self isOopCompiledMethod: newMethod) not]
+				ifFalse: [self assert: ((self isOopCompiledMethod: newMethod)
+									  and: [(self primitiveIndexOf: newMethod) ~= 0])].
+			 "Invoke an interpreter primitive (because the method is to be interpreted or has not yet been
+			  compiled).  This is very similar to invoking an interpreter primitive from a compiled primitive
+			  (see e.g. SimpleStackBasedCogit>>compileInterpreterPrimitive:).  Cut back the stack pointer
+			  (done above) to skip the return address and invoke the function.  On return if it has succeeded
+			  simply continue otherwise restore the stackPointer, collect the pc and interpret.  Note that
+			  frame building primitives such as primitiveClosureValue, primitiveEvaluateMethod et al will not
+			  return but will instead jump into either machine code or longjmp back to the interpreter."
+			"Assign stackPage headFP so we can tell if the primitive built a frame.  We can't simply save
+			 the framePointer since e.g. assignment to contexts (via primitiveInstVarAt:put:) can change the
+			 framePointer.  But context assignments will change both the framePointer and stackPage headFP."
+			 stackPage headFP: framePointer.
+			 self isPrimitiveFunctionPointerAnIndex
+				ifTrue:
+					[self externalQuickPrimitiveResponse.
+					 primFailCode := 0]
+				ifFalse:
+					[self slowPrimitiveResponse].
+			self successful ifTrue:
+				[self return: self popStack toExecutive: false
+				 "NOTREACHED"]]
+		ifFalse:
+			[self assert: ((self primitiveIndexOf: newMethod) = 0
+						or: [(self functionPointerFor: (self primitiveIndexOf: newMethod) inClass: objectMemory nilObject) = 0])].
+	"if not primitive, or primitive failed, activate the method and reenter the interpreter"
+	self activateNewMethod.
+	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
+	"NOTREACHED"
+	^nil! !
+!CoInterpreter methodsFor: 'enilopmarts' stamp: 'eem 12/30/2010 19:42' prior: 34626310!
+enterRegisterArgCogMethod: cogMethod at: entryOffset receiver: rcvr
+	"convert
+	 		rcvr	base
+			arg(s)
+			retpc	<- sp
+	 to
+			retpc	base
+			entrypc
+			rcvr
+			arg(s)	<- sp
+	 and then enter at either the checked or the unchecked entry-point."
+	<var: #cogMethod type: #'CogMethod *'>
+	self cppIf: cogit numRegArgs > 0
+		ifTrue:
+			[self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2]).
+			 cogMethod cmNumArgs = 2 ifTrue:
+				[self stackValue: 3 put: self stackTop. "retpc"
+				 self push: (self stackValue: 1). "last arg"
+				 self stackValue: 1 put: (self stackValue: 3). "first arg"
+				 self stackValue: 2 put: rcvr.
+				 self stackValue: 3 put: cogMethod asInteger + entryOffset.
+				 cogit ceEnterCogCodePopReceiverArg1Arg0Regs
+				"NOTREACHED"].
+			 cogMethod cmNumArgs = 1 ifTrue:
+				[self stackValue: 2 put: self stackTop. "retpc"
+				 self push: (self stackValue: 1). "arg"
+				 self stackValue: 1 put: rcvr.
+				 self stackValue: 2 put: cogMethod asInteger + entryOffset.
+				 cogit ceEnterCogCodePopReceiverArg0Regs
+				"NOTREACHED"].
+			 self assert: cogMethod cmNumArgs = 0.
+			 self stackValue: 1 put: self stackTop. "retpc"
+			 self stackValue: 0 put: cogMethod asInteger + entryOffset.
+			 self push: rcvr.
+			 cogit ceEnterCogCodePopReceiverReg
+			 "NOTREACHED"]
+		ifFalse:
+			[self assert: false]! !
+!Cogit methodsFor: 'method map' stamp: 'eem 12/31/2010 12:50' prior: 35234297!
+mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
+	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
+	 for each mcpc, bcpc pair in the map until the function returns non-zero,
+	 answering that result, or 0 if it fails to."
+	<api>
+	<var: #cogMethod type: #'CogBlockMethod *'>
+	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(char annotation, char *mcpc, sqInt bcpc, void *arg)'>
+	<var: #arg type: #'void *'>
+	| isInBlock mcpc bcpc endbcpc map mapByte firstTime homeMethod aMethodObj |
+	<var: #descriptor type: #'BytecodeDescriptor *'>
+	<var: #homeMethod type: #'CogMethod *'>
+	cogMethod cmType = CMMethod
+		ifTrue:
+			[isInBlock := false.
+			 mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
+			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
+			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
+			 map := self findMapLocationForMcpc: mcpc inMethod: homeMethod.
+			 self flag: 'I see crashes here or below but don''t see quite how the VM asks for and gets answered 0 here.'.
+			 self assert: map ~= 0.
+			 map = 0 ifTrue: [^0].
+			 self assert: ((coInterpreter byteAt: map) >> AnnotationShift = IsMethodReference
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsRelativeCall
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsDisplacementX2N]])]
+		ifFalse:
+			[isInBlock := true.
+			 mcpc := cogMethod asInteger + (self sizeof: CogBlockMethod).
+			 homeMethod := self cogHomeMethod: cogMethod.
+			 map := self findMapLocationForMcpc: mcpc inMethod: homeMethod.
+			 self flag: 'I see crashes here or above but don''t see quite how the VM asks for and gets answered 0 here.'.
+			 self assert: map ~= 0.
+			 map = 0 ifTrue: [^0].
+			 self assert: ((coInterpreter byteAt: map) >> AnnotationShift = HasBytecodePC "fiducial"
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsDisplacementX2N]).
+			 [(coInterpreter byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
+				[map := map - 1].
+			 map := map - 1]. "skip fiducial"
+	bcpc := startbcpc.
+	aMethodObj := homeMethod methodObject.
+	endbcpc := (objectMemory byteSizeOf: aMethodObj) - 1.
+	self assert: (bcpc >= (coInterpreter startPCOfMethod: aMethodObj)
+				and: [bcpc <= endbcpc]).
+	firstTime := true.
+	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
+		[| annotation bcpcArg result descriptor numBytes |
+		 mapByte >= FirstAnnotation
+			ifTrue:
+				[annotation := mapByte >> AnnotationShift.
+				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
+				(annotation = HasBytecodePC or: [annotation = IsSendCall])
+					ifTrue:
+						[| byte |
+						bcpcArg := bcpc.
+						byte := objectMemory fetchByte: bcpc ofObject: aMethodObj.
+						descriptor := self generatorAt: byte.
+						numBytes := descriptor numBytes.
+						 (bcpc = startbcpc
+						  and: [descriptor isMapped
+						  and: [firstTime]])
+							ifTrue:
+								["horrible special case for frame-building accessors in contexts, e.g.
+								  MethodContext>>method.  In this case the first bytecode is mapped
+								  and so counts twice, once for the stackCheckOffset and once for itself."
+								 firstTime := false]
+							ifFalse:
+								[bcpc := self nextBytecodePCFor: descriptor at: bcpc byte0: byte in: aMethodObj.
+								 bcpc := self nextBytecodePCInMapAfter: bcpc
+											in: aMethodObj
+											inBlock: isInBlock
+											upTo: endbcpc].
+						 self assert: bcpcArg ~= 0]
+					ifFalse: [bcpcArg := numBytes := 0].
+				 result := self perform: functionSymbol
+								with: annotation
+								with: (self cCoerceSimple: mcpc to: #'char *')
+								with: bcpcArg + numBytes
+								with: arg.
+				 result ~= 0 ifTrue:
+					[^result]]
+			ifFalse:
+				[mcpc := mcpc + (mapByte >= DisplacementX2N
+									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
+									ifFalse: [mapByte])].
+		 map := map - 1].
+	^0! !
+!Cogit methodsFor: 'disassembly' stamp: 'eem 12/30/2010 20:00' prior: 35411760!
+printMethodHeader: cogMethod on: aStream
+	<doNotGenerate>
+	self cCode: ''
+		inSmalltalk:
+			[cogMethod isInteger ifTrue:
+				[^self printMethodHeader: (coInterpreter cogMethodSurrogateAt: cogMethod) on: aStream]].
+	aStream ensureCr.
+	cogMethod asInteger printOn: aStream base: 16.
+	aStream crtab; nextPutAll: (cogMethod cmType ~= CMBlock ifTrue: ['objhdr: '] ifFalse: ['homemth: ']).
+	cogMethod objectHeader printOn: aStream base: 16.
+	aStream
+		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
+		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
+	cogMethod cmType ~= CMBlock ifTrue:
+		[aStream crtab; nextPutAll: 'blksiz: '.
+		cogMethod blockSize printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'method: '.
+		cogMethod methodObject printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'mthhdr: '.
+		cogMethod methodHeader printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'selctr: '.
+		cogMethod selector printOn: aStream base: 16.
+		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
+			[:string| aStream nextPut: $=; nextPutAll: string].
+		aStream crtab; nextPutAll: 'blkentry: '.
+		cogMethod blockEntryOffset printOn: aStream base: 16.
+		cogMethod blockEntryOffset ~= 0 ifTrue:
+			[aStream nextPutAll: ' => '.
+			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
+	cogMethod cmType = CMClosedPIC
+		ifTrue:
+			[aStream crtab; nextPutAll: 'cPICNumCases: '.
+			 cogMethod cPICNumCases printOn: aStream base: 16.]
+		ifFalse:
+			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
+			 cogMethod stackCheckOffset printOn: aStream base: 16.
+			 cogMethod stackCheckOffset > 0 ifTrue:
+				[aStream nextPut: $/.
+				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16]].
+	aStream cr; flush! !
+!CurrentImageCoInterpreterFacade methodsFor: 'labels' stamp: 'eem 12/31/2010 12:11' prior: 35523752!
+lookupAddress: address
+	^(objectMap
+		keyAtValue: address
+		ifAbsent:
+			[variables
+				keyAtValue: address
+				ifAbsent: [^nil]]) asString! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg and: reg2
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg1 and: reg2 and: reg3
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+
+SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+	instanceVariableNames: 'callerSavedRegMask methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs deadCode'
+	classVariableNames: ''
+	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
+	category: 'VMMaker-JIT'!
+!StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 38899170!
+StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
+
+See methods in the class-side documentation protocol for more detail.
+
+Instance Variables
+	callerSavedRegMask:							<Integer>
+	ceEnter0ArgsPIC:								<Integer>
+	ceEnter1ArgsPIC:								<Integer>
+	ceEnter2ArgsPIC:								<Integer>
+	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
+	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
+	debugBytecodePointers:						<Set of Integer>
+	debugFixupBreaks:								<Set of Integer>
+	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
+	methodAbortTrampolines:						<CArrayAccessor of Integer>
+	methodOrBlockNumTemps:						<Integer>
+	optStatus:										<Integer>
+	picAbortTrampolines:							<CArrayAccessor of Integer>
+	picMissTrampolines:							<CArrayAccessor of Integer>
+	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
+	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
+	regArgsHaveBeenPushed:						<Boolean>
+	simSelf:											<CogSimStackEntry>
+	simSpillBase:									<Integer>
+	simStack:										<CArrayAccessor of CogSimStackEntry>
+	simStackPtr:									<Integer>
+	traceSimStack:									<Integer>
+
+callerSavedRegMask
+	- the bitmask of the ABI's caller-saved registers
+
+ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
+	- the trampoline for entering an N-arg PIC
+
+ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
+	- teh trampoline for entering a method with N register args
+	
+debugBytecodePointers
+	- a Set of bytecode pcs for setting breakpoints (simulation only)
+
+debugFixupBreaks
+	- a Set of fixup indices for setting breakpoints (simulation only)
+
+debugStackPointers
+	- an Array of stack depths for each bytecode for code verification
+
+methodAbortTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+methodOrBlockNumTemps
+	- the number of method or block temps (including args) in the current compilation unit (method or block)
+
+optStatus
+	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
+
+picAbortTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+picMissTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
+	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
+
+regArgsHaveBeenPushed
+	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
+
+simSelf
+	- the simulation stack entry representing self in the current compilation unit
+
+simSpillBase
+	- the variable tracking how much of the simulation stack has been spilled to the real stack
+
+simStack
+	- the simulation stack itself
+
+simStackPtr
+	- the pointer to the top of the simulation stack
+!
+]style[(819 14 2308),cblack;,!
+!StackToRegisterMappingCogit methodsFor: 'compile abstract instructions' stamp: 'eem 12/30/2010 16:15' prior: 38815078!
+compileAbstractInstructionsFrom: start through: end
+	"Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course."
+	| nextOpcodeIndex descriptor fixup result |
+	<var: #descriptor type: #'BytecodeDescriptor *'>
+	<var: #fixup type: #'BytecodeFixup *'>
+	self traceSimStack.
+	bytecodePointer := start.
+	descriptor := nil.
+	deadCode := false.
+	[self cCode: '' inSmalltalk:
+		[(debugBytecodePointers includes: bytecodePointer) ifTrue: [self halt]].
+	fixup := self fixupAt: bytecodePointer - initialPC.
+	fixup targetInstruction asUnsignedInteger > 0
+		ifTrue:
+			[deadCode := false.
+	 		 fixup targetInstruction asUnsignedInteger >= 2 ifTrue:
+				[self merge: fixup afterReturn: (descriptor notNil and: [descriptor isReturn])]]
+		ifFalse: "If there's no fixup following a return there's no jump to that code and it is dead."
+			[(descriptor notNil and: [descriptor isReturn]) ifTrue:
+				[deadCode := true]].
+	 self cCode: '' inSmalltalk:
+		[deadCode ifFalse:
+			[self assert: simStackPtr + (needsFrame
+										ifTrue: [0]
+										ifFalse: [methodOrBlockNumArgs + 1])
+						= (self debugStackPointerFor: bytecodePointer)]].
+	 byte0 := objectMemory fetchByte: bytecodePointer ofObject: methodObj.
+	 descriptor := self generatorAt: byte0.
+	 descriptor numBytes > 1 ifTrue:
+		[byte1 := objectMemory fetchByte: bytecodePointer + 1 ofObject: methodObj.
+		 descriptor numBytes > 2 ifTrue:
+			[byte2 := objectMemory fetchByte: bytecodePointer + 2 ofObject: methodObj.
+			 descriptor numBytes > 3 ifTrue:
+				[byte3 := objectMemory fetchByte: bytecodePointer + 3 ofObject: methodObj.
+				 descriptor numBytes > 4 ifTrue:
+					[self notYetImplemented]]]].
+	 nextOpcodeIndex := opcodeIndex.
+	 result := deadCode
+				ifTrue: "insert nops for dead code that is mapped so that bc to mc mapping is not many to one"
+					[(descriptor isMapped
+					  or: [inBlock and: [descriptor isMappedInBlock]]) ifTrue:
+						[self annotateBytecode: self Nop].
+						0]
+				ifFalse:
+					[self perform: descriptor generator].
+	 self traceDescriptor: descriptor; traceSimStack.
+	 (fixup targetInstruction asUnsignedInteger between: 1 and: 2) ifTrue:
+		["There is a fixup for this bytecode.  It must point to the first generated
+		   instruction for this bytecode.  If there isn't one we need to add a label."
+		 opcodeIndex = nextOpcodeIndex ifTrue:
+			[self Label].
+		 fixup targetInstruction: (self abstractInstructionAt: nextOpcodeIndex)].
+	 bytecodePointer := self nextBytecodePCFor: descriptor at: bytecodePointer byte0: byte0 in: methodObj.
+	 result = 0 and: [bytecodePointer <= end]] whileTrue.
+	^result! !
+!StackToRegisterMappingCogit methodsFor: 'bytecode generators' stamp: 'eem 12/30/2010 16:22' prior: 38854414!
+genSpecialSelectorEqualsEquals
+	| argReg rcvrReg nextPC postBranchPC targetBytecodePC branchBytecode primDescriptor branchDescriptor jumpEqual jumpNotEqual resultReg |
+	<var: #primDescriptor type: #'BytecodeDescriptor *'>
+	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+	<var: #jumpEqual type: #'AbstractInstruction *'>
+	<var: #jumpNotEqual type: #'AbstractInstruction *'>
+	self ssPop: 2.
+	resultReg := self availableRegisterOrNil.
+	resultReg ifNil:
+		[self ssAllocateRequiredReg: (resultReg := Arg1Reg)].
+	self ssPush: 2.
+	(self ssTop type = SSConstant
+	 and: [self ssTop spilled not]) "if spilled we must generate a real pop"
+		ifTrue:
+			[(self ssValue: 1) type = SSRegister
+				ifTrue: [rcvrReg := (self ssValue: 1) register]
+				ifFalse:
+					[(self ssValue: 1) popToReg: (rcvrReg := resultReg)].
+			(objectRepresentation shouldAnnotateObjectReference: self ssTop constant)
+				ifTrue: [self annotate: (self CmpCw: self ssTop constant R: rcvrReg)
+							objRef: self ssTop constant]
+				ifFalse: [self CmpCq: self ssTop constant R: rcvrReg].
+			self ssPop: 1]
+		ifFalse:
+			[argReg := self ssStorePop: true toPreferredReg: TempReg.
+			 rcvrReg := argReg = resultReg
+							ifTrue: [TempReg]
+							ifFalse: [resultReg].
+			self ssTop popToReg: rcvrReg.
+			self CmpR: argReg R: rcvrReg].
+	self ssPop: 1; ssPushRegister: resultReg.
+	primDescriptor := self generatorAt: byte0.
+	nextPC := bytecodePointer + primDescriptor numBytes.
+	branchBytecode := objectMemory fetchByte: nextPC ofObject: methodObj.
+	branchDescriptor := self generatorAt: branchBytecode.
+	(branchDescriptor isBranchTrue
+	 or: [branchDescriptor isBranchFalse])
+		ifTrue:
+			[self ssFlushTo: simStackPtr - 1.
+			 targetBytecodePC := nextPC
+								+ branchDescriptor numBytes
+								+ (self spanFor: branchDescriptor at: nextPC byte0: branchBytecode in: methodObj).
+			 postBranchPC := nextPC + branchDescriptor numBytes.
+			 (self fixupAt: nextPC - initialPC) targetInstruction = 0 ifTrue: "The next instruction is dead.  we can skip it."
+				[deadCode := true.
+				 self ssPop: 1. "the conditional branch bytecodes pop the item tested from the stack."
+				 self ensureFixupAt: targetBytecodePC - initialPC.
+				 self ensureFixupAt: postBranchPC - initialPC].
+			 self gen: (branchDescriptor isBranchTrue
+						ifTrue: [JumpZero]
+						ifFalse: [JumpNonZero])
+				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+			 self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)]
+		ifFalse:
+			[jumpNotEqual := self JumpNonZero: 0.
+			 self annotate: (self MoveCw: objectMemory trueObject R: resultReg)
+				objRef: objectMemory trueObject.
+			 jumpEqual := self Jump: 0.
+			 jumpNotEqual jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: resultReg)
+											objRef: objectMemory falseObject).
+			 jumpEqual jmpTarget: self Label].
+	resultReg == ReceiverResultReg ifTrue:
+		[optStatus isReceiverResultRegLive: false].
+	^0! !
+
+----End fileIn of /Users/eliot/Cog/methods.st----!
+
+----STARTUP----{31 December 2010 . 7:05:55 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 31 December 2010 at 7:05:24 pm'!
+!CoInterpreter methodsFor: 'trampolines' stamp: 'eem 12/31/2010 19:03' prior: 34481786!
+activateInterpreterMethodFromMachineCode
+	"Execute an interpreted method from machine code.  We assume (require) that newMethod
+	 messageSelector, primitiveFunctionPointer and argumentCount have been set in the caller.
+	 Once evaluated either continue in the interpreter via a jongjmp or in machine code via an
+	 enilopmart (a form of longjmp - a stinking rose by any other name)."
+	<inline: false>
+	cogit assertCStackWellAligned.
+	self assert: (self validInstructionPointer: self stackTop inFrame: framePointer).
+	instructionPointer := self popStack.
+	primitiveFunctionPointer ~= 0
+		ifTrue:
+			[primitiveFunctionPointer = #primitiveInvokeObjectAsMethod asSymbol
+				ifTrue: [self assert: (objectMemory isOopCompiledMethod: newMethod) not]
+				ifFalse: [self assert: ((objectMemory isOopCompiledMethod: newMethod)
+									  and: [(self primitiveIndexOf: newMethod) ~= 0])].
+			 "Invoke an interpreter primitive (because the method is to be interpreted or has not yet been
+			  compiled).  This is very similar to invoking an interpreter primitive from a compiled primitive
+			  (see e.g. SimpleStackBasedCogit>>compileInterpreterPrimitive:).  Cut back the stack pointer
+			  (done above) to skip the return address and invoke the function.  On return if it has succeeded
+			  simply continue otherwise restore the stackPointer, collect the pc and interpret.  Note that
+			  frame building primitives such as primitiveClosureValue, primitiveEvaluateMethod et al will not
+			  return but will instead jump into either machine code or longjmp back to the interpreter."
+			"Assign stackPage headFP so we can tell if the primitive built a frame.  We can't simply save
+			 the framePointer since e.g. assignment to contexts (via primitiveInstVarAt:put:) can change the
+			 framePointer.  But context assignments will change both the framePointer and stackPage headFP."
+			 stackPage headFP: framePointer.
+			 self isPrimitiveFunctionPointerAnIndex
+				ifTrue:
+					[self externalQuickPrimitiveResponse.
+					 primFailCode := 0]
+				ifFalse:
+					[self slowPrimitiveResponse].
+			self successful ifTrue:
+				[self return: self popStack toExecutive: false
+				 "NOTREACHED"]]
+		ifFalse:
+			[self assert: ((self primitiveIndexOf: newMethod) = 0
+						or: [(self functionPointerFor: (self primitiveIndexOf: newMethod) inClass: objectMemory nilObject) = 0])].
+	"if not primitive, or primitive failed, activate the method and reenter the interpreter"
+	self activateNewMethod.
+	self siglong: reenterInterpreter jmp: ReturnToInterpreter.
+	"NOTREACHED"
+	^nil! !
+!CoInterpreter methodsFor: 'enilopmarts' stamp: 'eem 12/30/2010 19:42' prior: 34626310!
+enterRegisterArgCogMethod: cogMethod at: entryOffset receiver: rcvr
+	"convert
+	 		rcvr	base
+			arg(s)
+			retpc	<- sp
+	 to
+			retpc	base
+			entrypc
+			rcvr
+			arg(s)	<- sp
+	 and then enter at either the checked or the unchecked entry-point."
+	<var: #cogMethod type: #'CogMethod *'>
+	self cppIf: cogit numRegArgs > 0
+		ifTrue:
+			[self assert: (cogit numRegArgs > 0 and: [cogit numRegArgs <= 2]).
+			 cogMethod cmNumArgs = 2 ifTrue:
+				[self stackValue: 3 put: self stackTop. "retpc"
+				 self push: (self stackValue: 1). "last arg"
+				 self stackValue: 1 put: (self stackValue: 3). "first arg"
+				 self stackValue: 2 put: rcvr.
+				 self stackValue: 3 put: cogMethod asInteger + entryOffset.
+				 cogit ceEnterCogCodePopReceiverArg1Arg0Regs
+				"NOTREACHED"].
+			 cogMethod cmNumArgs = 1 ifTrue:
+				[self stackValue: 2 put: self stackTop. "retpc"
+				 self push: (self stackValue: 1). "arg"
+				 self stackValue: 1 put: rcvr.
+				 self stackValue: 2 put: cogMethod asInteger + entryOffset.
+				 cogit ceEnterCogCodePopReceiverArg0Regs
+				"NOTREACHED"].
+			 self assert: cogMethod cmNumArgs = 0.
+			 self stackValue: 1 put: self stackTop. "retpc"
+			 self stackValue: 0 put: cogMethod asInteger + entryOffset.
+			 self push: rcvr.
+			 cogit ceEnterCogCodePopReceiverReg
+			 "NOTREACHED"]
+		ifFalse:
+			[self assert: false]! !
+!Cogit methodsFor: 'method map' stamp: 'eem 12/31/2010 14:54' prior: 35226074!
+bytecodePCFor: mcpc startBcpc: startbcpc in: cogMethod
+	"Answer the zero-relative bytecode pc matching the machine code pc argument in
+	 cogMethod, given the start of the bytecodes for cogMethod's block or method object."
+	<api>
+	<var: #cogMethod type: #'CogBlockMethod *'>
+	"All map entries for bytecodes (sends, mustBeBooleans et al) map to the following
+	 bytecode except the first bytecode (stackCheckOffset).  So special case that here."
+	mcpc = (cogMethod stackCheckOffset = 0
+				ifTrue: [cogMethod asInteger + (self sizeof: CogBlockMethod)]
+				ifFalse: [cogMethod asInteger + cogMethod stackCheckOffset]) ifTrue:
+		[^startbcpc].
+	^self
+		mapFor: cogMethod
+		bcpc: startbcpc
+		performUntil: #find:Mcpc:Bcpc:MatchingMcpc: asSymbol
+		arg: (self cCoerceSimple: mcpc to: #'void *')! !
+!Cogit methodsFor: 'method map' stamp: 'eem 12/31/2010 14:10' prior: 35229086!
+findBlockMethodWithStartMcpc: blockEntryPC bcpc: startBcpc
+	<returnTypeC: #usqInt>
+	| cogBlockMethod startMcpc |
+	<var: #cogBlockMethod type: #'CogBlockMethod *'>
+	cogBlockMethod := self cCoerceSimple: blockEntryPC - (self sizeof: CogBlockMethod)
+								   to: #'CogBlockMethod *'.
+	startMcpc := cogBlockMethod stackCheckOffset = 0
+					ifTrue: [cogBlockMethod] "frameless block method"
+					ifFalse: [cogBlockMethod asUnsignedInteger + cogBlockMethod stackCheckOffset].
+	(self bytecodePCFor: startMcpc startBcpc: startBcpc in: cogBlockMethod) = startBcpc ifTrue:
+		[^cogBlockMethod asUnsignedInteger].
+	^0 "keep scanning..."! !
+!Cogit methodsFor: 'method map' stamp: 'eem 12/31/2010 14:09' prior: 35231138!
+findMethodForStartBcpc: startbcpc inHomeMethod: cogMethod
+	<api>
+	<var: #cogMethod type: #'CogMethod *'>
+	<returnTypeC: #'CogBlockMethod *'>
+	"Find the CMMethod or CMBlock that has zero-relative startbcpc as its first bytecode pc.
+	 As this is for cannot resume processing and/or conversion to machine-code on backward
+	 branch, it doesn't have to be fast.  Enumerate block returns and map to bytecode pcs."
+	self assert: cogMethod cmType = CMMethod.
+	startbcpc = (coInterpreter startPCOfMethodHeader: cogMethod methodHeader) ifTrue:
+		[^self cCoerceSimple: cogMethod to: #'CogBlockMethod *'].
+	self assert: cogMethod blockEntryOffset ~= 0.
+	^self cCoerceSimple: (self blockDispatchTargetsFor: cogMethod
+								perform: #findBlockMethodWithStartMcpc:bcpc: asSymbol
+								arg: startbcpc)
+		to: #'CogBlockMethod *'! !
+!Cogit methodsFor: 'method map' stamp: 'eem 12/31/2010 14:25' prior: 35234297!
+mapFor: cogMethod bcpc: startbcpc performUntil: functionSymbol arg: arg
+	"Machine-code <-> bytecode pc mapping support.  Evaluate functionSymbol
+	 for each mcpc, bcpc pair in the map until the function returns non-zero,
+	 answering that result, or 0 if it fails to."
+	<api>
+	<var: #cogMethod type: #'CogBlockMethod *'>
+	<var: #functionSymbol declareC: 'sqInt (*functionSymbol)(char annotation, char *mcpc, sqInt bcpc, void *arg)'>
+	<var: #arg type: #'void *'>
+	| isInBlock mcpc bcpc endbcpc map mapByte firstTime homeMethod aMethodObj |
+	<var: #descriptor type: #'BytecodeDescriptor *'>
+	<var: #homeMethod type: #'CogMethod *'>
+	cogMethod cmType = CMMethod
+		ifTrue:
+			[isInBlock := false.
+			 mcpc := cogMethod asInteger + cmNoCheckEntryOffset.
+			 homeMethod := self cCoerceSimple: cogMethod to: #'CogMethod *'.
+			 self assert: startbcpc = (coInterpreter startPCOfMethodHeader: homeMethod methodHeader).
+			 map := self findMapLocationForMcpc: mcpc inMethod: homeMethod.
+			 self assert: map ~= 0.
+			 map = 0 ifTrue: [^0].
+			 self assert: ((coInterpreter byteAt: map) >> AnnotationShift = IsMethodReference
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsRelativeCall
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsDisplacementX2N]])]
+		ifFalse:
+			[isInBlock := true.
+			 mcpc := cogMethod asInteger + (self sizeof: CogBlockMethod).
+			 homeMethod := self cogHomeMethod: cogMethod.
+			 map := self findMapLocationForMcpc: mcpc inMethod: homeMethod.
+			 self assert: map ~= 0.
+			 map = 0 ifTrue: [^0].
+			 self assert: ((coInterpreter byteAt: map) >> AnnotationShift = HasBytecodePC "fiducial"
+						 or: [(coInterpreter byteAt: map) >> AnnotationShift = IsDisplacementX2N]).
+			 [(coInterpreter byteAt: map) >> AnnotationShift ~= HasBytecodePC] whileTrue:
+				[map := map - 1].
+			 map := map - 1]. "skip fiducial"
+	bcpc := startbcpc.
+	aMethodObj := homeMethod methodObject.
+	endbcpc := (objectMemory byteSizeOf: aMethodObj) - 1.
+	self assert: (bcpc >= (coInterpreter startPCOfMethod: aMethodObj)
+				and: [bcpc <= endbcpc]).
+	firstTime := true.
+	[(mapByte := objectMemory byteAt: map) ~= MapEnd] whileTrue:
+		[| annotation bcpcArg result descriptor numBytes |
+		 mapByte >= FirstAnnotation
+			ifTrue:
+				[annotation := mapByte >> AnnotationShift.
+				mcpc := mcpc + (mapByte bitAnd: DisplacementMask).
+				(annotation = HasBytecodePC or: [annotation = IsSendCall])
+					ifTrue:
+						[| byte |
+						bcpcArg := bcpc.
+						byte := objectMemory fetchByte: bcpc ofObject: aMethodObj.
+						descriptor := self generatorAt: byte.
+						numBytes := descriptor numBytes.
+						 (bcpc = startbcpc
+						  and: [descriptor isMapped
+						  and: [firstTime]])
+							ifTrue:
+								["horrible special case for frame-building accessors in contexts, e.g.
+								  MethodContext>>method.  In this case the first bytecode is mapped
+								  and so counts twice, once for the stackCheckOffset and once for itself."
+								 firstTime := false]
+							ifFalse:
+								[bcpc := self nextBytecodePCFor: descriptor at: bcpc byte0: byte in: aMethodObj.
+								 bcpc := self nextBytecodePCInMapAfter: bcpc
+											in: aMethodObj
+											inBlock: isInBlock
+											upTo: endbcpc].
+						 self assert: bcpcArg ~= 0]
+					ifFalse: [bcpcArg := numBytes := 0].
+				 result := self perform: functionSymbol
+								with: annotation
+								with: (self cCoerceSimple: mcpc to: #'char *')
+								with: bcpcArg + numBytes
+								with: arg.
+				 result ~= 0 ifTrue:
+					[^result]]
+			ifFalse:
+				[mcpc := mcpc + (mapByte >= DisplacementX2N
+									ifTrue: [mapByte - DisplacementX2N << AnnotationShift]
+									ifFalse: [mapByte])].
+		 map := map - 1].
+	^0! !
+!Cogit methodsFor: 'disassembly' stamp: 'eem 12/30/2010 20:00' prior: 35411760!
+printMethodHeader: cogMethod on: aStream
+	<doNotGenerate>
+	self cCode: ''
+		inSmalltalk:
+			[cogMethod isInteger ifTrue:
+				[^self printMethodHeader: (coInterpreter cogMethodSurrogateAt: cogMethod) on: aStream]].
+	aStream ensureCr.
+	cogMethod asInteger printOn: aStream base: 16.
+	aStream crtab; nextPutAll: (cogMethod cmType ~= CMBlock ifTrue: ['objhdr: '] ifFalse: ['homemth: ']).
+	cogMethod objectHeader printOn: aStream base: 16.
+	aStream
+		crtab; nextPutAll: 'nArgs: ';	print: cogMethod cmNumArgs;
+		tab;    nextPutAll: 'type: ';	print: cogMethod cmType.
+	cogMethod cmType ~= CMBlock ifTrue:
+		[aStream crtab; nextPutAll: 'blksiz: '.
+		cogMethod blockSize printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'method: '.
+		cogMethod methodObject printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'mthhdr: '.
+		cogMethod methodHeader printOn: aStream base: 16.
+		aStream crtab; nextPutAll: 'selctr: '.
+		cogMethod selector printOn: aStream base: 16.
+		(coInterpreter lookupAddress: cogMethod selector) ifNotNil:
+			[:string| aStream nextPut: $=; nextPutAll: string].
+		aStream crtab; nextPutAll: 'blkentry: '.
+		cogMethod blockEntryOffset printOn: aStream base: 16.
+		cogMethod blockEntryOffset ~= 0 ifTrue:
+			[aStream nextPutAll: ' => '.
+			 cogMethod asInteger + cogMethod blockEntryOffset printOn: aStream base: 16]].
+	cogMethod cmType = CMClosedPIC
+		ifTrue:
+			[aStream crtab; nextPutAll: 'cPICNumCases: '.
+			 cogMethod cPICNumCases printOn: aStream base: 16.]
+		ifFalse:
+			[aStream crtab; nextPutAll: 'stackCheckOffset: '.
+			 cogMethod stackCheckOffset printOn: aStream base: 16.
+			 cogMethod stackCheckOffset > 0 ifTrue:
+				[aStream nextPut: $/.
+				 cogMethod asInteger + cogMethod stackCheckOffset printOn: aStream base: 16]].
+	aStream cr; flush! !
+!CurrentImageCoInterpreterFacade methodsFor: 'labels' stamp: 'eem 12/31/2010 12:11' prior: 35523752!
+lookupAddress: address
+	^(objectMap
+		keyAtValue: address
+		ifAbsent:
+			[variables
+				keyAtValue: address
+				ifAbsent: [^nil]]) asString! !
+!SimpleStackBasedCogit methodsFor: 'compile abstract instructions' stamp: 'eem 12/31/2010 14:32' prior: 37974309!
+compileBlockFramelessEntry: blockStart
+	"Make sure ReceiverResultReg holds the receiver, loaded from the closure,
+	 which is what is initially in ReceiverResultReg.  We must annotate the first
+	 instruction so that findMethodForStartBcpc:inHomeMethod: can function.
+	 We need two annotations because the first is a fiducial."
+	<var: #blockStart type: #'BlockStart *'>
+	self annotateBytecode: blockStart entryLabel.
+	self annotateBytecode: blockStart entryLabel.
+	objectRepresentation
+		genLoadSlot: ClosureOuterContextIndex
+			sourceReg: ReceiverResultReg
+				destReg: TempReg;
+		genLoadSlot: ReceiverIndex
+			sourceReg: TempReg
+				destReg: ReceiverResultReg! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg and: reg2
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+!SimpleStackBasedCogit methodsFor: 'simulation stack' stamp: 'eem 12/30/2010 19:57'!
+registerMaskFor: reg1 and: reg2 and: reg3
+	"Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	 which doesn't get pruned due to Slang limitations."
+	^0! !
+
+SimpleStackBasedCogit subclass: #StackToRegisterMappingCogit
+	instanceVariableNames: 'callerSavedRegMask methodOrBlockNumTemps regArgsHaveBeenPushed simSelf simStack simStackPtr simSpillBase optStatus ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs methodAbortTrampolines picAbortTrampolines picMissTrampolines ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC debugStackPointers debugFixupBreaks debugBytecodePointers realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs deadCode'
+	classVariableNames: ''
+	poolDictionaries: 'CogCompilationConstants VMMethodCacheConstants VMObjectIndices VMStackFrameOffsets'
+	category: 'VMMaker-JIT'!
+!StackToRegisterMappingCogit commentStamp: 'eem 12/19/2010 18:12' prior: 38899170!
+StackToRegisterMappingCogit is an optimizing code generator that eliminates a lot of stack operations and inlines some special selector arithmetic.  It does so by a simple stack-to-register mapping scheme based on deferring the generation of code to produce operands until operand-consuming operations.  The operations that consume operands are sends, stores and returns.
+
+See methods in the class-side documentation protocol for more detail.
+
+Instance Variables
+	callerSavedRegMask:							<Integer>
+	ceEnter0ArgsPIC:								<Integer>
+	ceEnter1ArgsPIC:								<Integer>
+	ceEnter2ArgsPIC:								<Integer>
+	ceEnterCogCodePopReceiverArg0Regs:		<Integer>
+	ceEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
+	debugBytecodePointers:						<Set of Integer>
+	debugFixupBreaks:								<Set of Integer>
+	debugStackPointers:							<CArrayAccessor of (Integer|nil)>
+	methodAbortTrampolines:						<CArrayAccessor of Integer>
+	methodOrBlockNumTemps:						<Integer>
+	optStatus:										<Integer>
+	picAbortTrampolines:							<CArrayAccessor of Integer>
+	picMissTrampolines:							<CArrayAccessor of Integer>
+	realCEEnterCogCodePopReceiverArg0Regs:		<Integer>
+	realCEEnterCogCodePopReceiverArg1Arg0Regs:	<Integer>
+	regArgsHaveBeenPushed:						<Boolean>
+	simSelf:											<CogSimStackEntry>
+	simSpillBase:									<Integer>
+	simStack:										<CArrayAccessor of CogSimStackEntry>
+	simStackPtr:									<Integer>
+	traceSimStack:									<Integer>
+
+callerSavedRegMask
+	- the bitmask of the ABI's caller-saved registers
+
+ceEnter0ArgsPIC ceEnter1ArgsPIC ceEnter2ArgsPIC
+	- the trampoline for entering an N-arg PIC
+
+ceEnterCogCodePopReceiverArg0Regs ceEnterCogCodePopReceiverArg1Arg0Regs
+	- teh trampoline for entering a method with N register args
+	
+debugBytecodePointers
+	- a Set of bytecode pcs for setting breakpoints (simulation only)
+
+debugFixupBreaks
+	- a Set of fixup indices for setting breakpoints (simulation only)
+
+debugStackPointers
+	- an Array of stack depths for each bytecode for code verification
+
+methodAbortTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+methodOrBlockNumTemps
+	- the number of method or block temps (including args) in the current compilation unit (method or block)
+
+optStatus
+	- the variable used to track the status of ReceiverResultReg for avoiding reloading that register with self between adjacent inst var accesses
+
+picAbortTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+picMissTrampolines
+	- a CArrayAccessor of abort trampolines for 0, 1, 2 and N args
+
+realCEEnterCogCodePopReceiverArg0Regs realCEEnterCogCodePopReceiverArg1Arg0Regs
+	- the real trampolines for ebtering machine code with N reg args when in the Debug regime
+
+regArgsHaveBeenPushed
+	- whether the register args have been pushed before frame build (e.g. when an interpreter primitive is called)
+
+simSelf
+	- the simulation stack entry representing self in the current compilation unit
+
+simSpillBase
+	- the variable tracking how much of the simulation stack has been spilled to the real stack
+
+simStack
+	- the simulation stack itself
+
+simStackPtr
+	- the pointer to the top of the simulation stack
+!
+]style[(819 14 2308),cblack;,!
+!StackToRegisterMappingCogit methodsFor: 'compile abstract instructions' stamp: 'eem 12/30/2010 16:15' prior: 38815078!
+compileAbstractInstructionsFrom: start through: end
+	"Loop over bytecodes, dispatching to the generator for each bytecode, handling fixups in due course."
+	| nextOpcodeIndex descriptor fixup result |
+	<var: #descriptor type: #'BytecodeDescriptor *'>
+	<var: #fixup type: #'BytecodeFixup *'>
+	self traceSimStack.
+	bytecodePointer := start.
+	descriptor := nil.
+	deadCode := false.
+	[self cCode: '' inSmalltalk:
+		[(debugBytecodePointers includes: bytecodePointer) ifTrue: [self halt]].
+	fixup := self fixupAt: bytecodePointer - initialPC.
+	fixup targetInstruction asUnsignedInteger > 0
+		ifTrue:
+			[deadCode := false.
+	 		 fixup targetInstruction asUnsignedInteger >= 2 ifTrue:
+				[self merge: fixup afterReturn: (descriptor notNil and: [descriptor isReturn])]]
+		ifFalse: "If there's no fixup following a return there's no jump to that code and it is dead."
+			[(descriptor notNil and: [descriptor isReturn]) ifTrue:
+				[deadCode := true]].
+	 self cCode: '' inSmalltalk:
+		[deadCode ifFalse:
+			[self assert: simStackPtr + (needsFrame
+										ifTrue: [0]
+										ifFalse: [methodOrBlockNumArgs + 1])
+						= (self debugStackPointerFor: bytecodePointer)]].
+	 byte0 := objectMemory fetchByte: bytecodePointer ofObject: methodObj.
+	 descriptor := self generatorAt: byte0.
+	 descriptor numBytes > 1 ifTrue:
+		[byte1 := objectMemory fetchByte: bytecodePointer + 1 ofObject: methodObj.
+		 descriptor numBytes > 2 ifTrue:
+			[byte2 := objectMemory fetchByte: bytecodePointer + 2 ofObject: methodObj.
+			 descriptor numBytes > 3 ifTrue:
+				[byte3 := objectMemory fetchByte: bytecodePointer + 3 ofObject: methodObj.
+				 descriptor numBytes > 4 ifTrue:
+					[self notYetImplemented]]]].
+	 nextOpcodeIndex := opcodeIndex.
+	 result := deadCode
+				ifTrue: "insert nops for dead code that is mapped so that bc to mc mapping is not many to one"
+					[(descriptor isMapped
+					  or: [inBlock and: [descriptor isMappedInBlock]]) ifTrue:
+						[self annotateBytecode: self Nop].
+						0]
+				ifFalse:
+					[self perform: descriptor generator].
+	 self traceDescriptor: descriptor; traceSimStack.
+	 (fixup targetInstruction asUnsignedInteger between: 1 and: 2) ifTrue:
+		["There is a fixup for this bytecode.  It must point to the first generated
+		   instruction for this bytecode.  If there isn't one we need to add a label."
+		 opcodeIndex = nextOpcodeIndex ifTrue:
+			[self Label].
+		 fixup targetInstruction: (self abstractInstructionAt: nextOpcodeIndex)].
+	 bytecodePointer := self nextBytecodePCFor: descriptor at: bytecodePointer byte0: byte0 in: methodObj.
+	 result = 0 and: [bytecodePointer <= end]] whileTrue.
+	^result! !
+!StackToRegisterMappingCogit methodsFor: 'bytecode generators' stamp: 'eem 12/30/2010 16:22' prior: 38854414!
+genSpecialSelectorEqualsEquals
+	| argReg rcvrReg nextPC postBranchPC targetBytecodePC branchBytecode primDescriptor branchDescriptor jumpEqual jumpNotEqual resultReg |
+	<var: #primDescriptor type: #'BytecodeDescriptor *'>
+	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
+	<var: #jumpEqual type: #'AbstractInstruction *'>
+	<var: #jumpNotEqual type: #'AbstractInstruction *'>
+	self ssPop: 2.
+	resultReg := self availableRegisterOrNil.
+	resultReg ifNil:
+		[self ssAllocateRequiredReg: (resultReg := Arg1Reg)].
+	self ssPush: 2.
+	(self ssTop type = SSConstant
+	 and: [self ssTop spilled not]) "if spilled we must generate a real pop"
+		ifTrue:
+			[(self ssValue: 1) type = SSRegister
+				ifTrue: [rcvrReg := (self ssValue: 1) register]
+				ifFalse:
+					[(self ssValue: 1) popToReg: (rcvrReg := resultReg)].
+			(objectRepresentation shouldAnnotateObjectReference: self ssTop constant)
+				ifTrue: [self annotate: (self CmpCw: self ssTop constant R: rcvrReg)
+							objRef: self ssTop constant]
+				ifFalse: [self CmpCq: self ssTop constant R: rcvrReg].
+			self ssPop: 1]
+		ifFalse:
+			[argReg := self ssStorePop: true toPreferredReg: TempReg.
+			 rcvrReg := argReg = resultReg
+							ifTrue: [TempReg]
+							ifFalse: [resultReg].
+			self ssTop popToReg: rcvrReg.
+			self CmpR: argReg R: rcvrReg].
+	self ssPop: 1; ssPushRegister: resultReg.
+	primDescriptor := self generatorAt: byte0.
+	nextPC := bytecodePointer + primDescriptor numBytes.
+	branchBytecode := objectMemory fetchByte: nextPC ofObject: methodObj.
+	branchDescriptor := self generatorAt: branchBytecode.
+	(branchDescriptor isBranchTrue
+	 or: [branchDescriptor isBranchFalse])
+		ifTrue:
+			[self ssFlushTo: simStackPtr - 1.
+			 targetBytecodePC := nextPC
+								+ branchDescriptor numBytes
+								+ (self spanFor: branchDescriptor at: nextPC byte0: branchBytecode in: methodObj).
+			 postBranchPC := nextPC + branchDescriptor numBytes.
+			 (self fixupAt: nextPC - initialPC) targetInstruction = 0 ifTrue: "The next instruction is dead.  we can skip it."
+				[deadCode := true.
+				 self ssPop: 1. "the conditional branch bytecodes pop the item tested from the stack."
+				 self ensureFixupAt: targetBytecodePC - initialPC.
+				 self ensureFixupAt: postBranchPC - initialPC].
+			 self gen: (branchDescriptor isBranchTrue
+						ifTrue: [JumpZero]
+						ifFalse: [JumpNonZero])
+				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
+			 self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)]
+		ifFalse:
+			[jumpNotEqual := self JumpNonZero: 0.
+			 self annotate: (self MoveCw: objectMemory trueObject R: resultReg)
+				objRef: objectMemory trueObject.
+			 jumpEqual := self Jump: 0.
+			 jumpNotEqual jmpTarget: (self annotate: (self MoveCw: objectMemory falseObject R: resultReg)
+											objRef: objectMemory falseObject).
+			 jumpEqual jmpTarget: self Label].
+	resultReg == ReceiverResultReg ifTrue:
+		[optStatus isReceiverResultRegLive: false].
+	^0! !
+
+----End fileIn of /Users/eliot/Cog/methods.st----!
+
+----QUIT----{31 December 2010 . 7:07:01 pm} VMMaker-Squeak4.1.image priorSource: 6053307!
+
+----STARTUP----{31 December 2010 . 7:12:03 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+SimpleStackBasedCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+----QUIT/NOSAVE----{31 December 2010 . 7:13:08 pm} VMMaker-Squeak4.1.image priorSource: 6098879!
+
+----STARTUP----{31 December 2010 . 7:14:09 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+StackToRegisterMappingCogit initializeBytecodeTableForClosureV3!
+
+----QUIT/NOSAVE----{31 December 2010 . 7:15:30 pm} VMMaker-Squeak4.1.image priorSource: 6098879!
+
+----STARTUP----{31 December 2010 . 7:15:37 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{31 December 2010 . 7:16:07 pm} VMMaker-Squeak4.1.image priorSource: 6098879!
+
+----STARTUP----{31 December 2010 . 7:21:40 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!Gnuifier methodsFor: 'as yet unclassified' stamp: 'eem 12/31/2010 19:18' prior: 35891606!
+gnuifyFrom: inFileStream to: outFileStream
+
+"convert interp.c to use GNU features"
+
+	| inData beforeInterpret inInterpret inInterpretVars beforePrimitiveResponse inPrimitiveResponse |
+
+	inData := inFileStream upToEnd withSqueakLineEndings.
+	inFileStream close.
+
+	"print a header"
+	outFileStream
+		nextPutAll: '/* This file has been post-processed for GNU C */';
+		cr; cr; cr.
+
+	beforeInterpret := true.    "whether we are before the beginning of interpret()"
+	inInterpret := false.     "whether we are in the middle of interpret"
+	inInterpretVars := false.    "whether we are in the variables of interpret"
+	beforePrimitiveResponse := true.  "whether we are before the beginning of primitiveResponse()"
+	inPrimitiveResponse := false.   "whether we are inside of primitiveResponse"
+	'Gnuifying'
+		displayProgressAt: Sensor cursorPoint
+		from: 1 to: (inData occurrencesOf: Character cr)
+		during:
+			[:bar | | lineNumber |
+			lineNumber := 0.
+			inData linesDo:
+				[ :inLine | | outLine extraOutLine |
+				bar value: (lineNumber := lineNumber + 1).
+				outLine := inLine. 	"print out one line for each input line; by default, print out the line that was input, but some rules modify it"
+				extraOutLine := nil.   "occasionally print a second output line..."
+				beforeInterpret ifTrue: [
+					(inLine = '#include "sq.h"') ifTrue: [
+						outLine := '#include "sqGnu.h"'. ].
+					(inLine beginsWith: 'interpret(void)') ifTrue: [
+						"reached the beginning of interpret"
+						beforeInterpret := false.
+						inInterpret := true.
+						inInterpretVars := true. ] ]
+				ifFalse: [
+				inInterpretVars ifTrue: [
+					(inLine findString: 'register struct foo * foo = &fum;') > 0 ifTrue: [
+						outLine := 'register struct foo * foo FOO_REG = &fum;' ].
+					(inLine findString: ' localIP;') > 0 ifTrue: [
+						outLine := '    char* localIP IP_REG;' ].
+					(inLine findString: ' localFP;') > 0 ifTrue: [
+						outLine := '    char* localFP FP_REG;' ].
+					(inLine findString: ' localSP;') > 0 ifTrue: [
+						outLine := '    char* localSP SP_REG;' ].
+					(inLine findString: ' currentBytecode;') > 0 ifTrue: [
+						outLine := '    sqInt currentBytecode CB_REG;' ].
+					inLine isEmpty ifTrue: [
+						"reached end of variables"
+						inInterpretVars := false.
+						outLine := '    JUMP_TABLE;'.
+						extraOutLine := inLine ] ]
+				ifFalse: [
+				inInterpret ifTrue: [
+					"working inside interpret(); translate the switch statement"
+					(inLine beginsWith: '		case ') ifTrue: [
+						| caseLabel |
+						caseLabel := (inLine findTokens: '	 :') second.
+						outLine := '		CASE(', caseLabel, ')' ].
+					inLine = '			break;' ifTrue: [
+						outLine := '			BREAK;' ].
+					inLine = '}' ifTrue: [
+						"all finished with interpret()"
+						inInterpret := false. ] ]
+				ifFalse: [
+				beforePrimitiveResponse ifTrue: [
+					(inLine beginsWith: 'primitiveResponse(') ifTrue: [
+						"into primitiveResponse we go"
+						beforePrimitiveResponse := false.
+						inPrimitiveResponse := true.
+						extraOutLine := '    PRIM_TABLE;'.  ] ]
+				ifFalse: [
+				inPrimitiveResponse ifTrue: [
+					(inLine = '	switch (primitiveIndex) {') ifTrue: [
+						extraOutLine := outLine.
+						outLine := '	PRIM_DISPATCH;' ].
+					(inLine = '	switch (GIV(primitiveIndex)) {') ifTrue: [
+						extraOutLine := outLine.
+						outLine := '	PRIM_DISPATCH;' ].
+					(inLine beginsWith: '	case ') ifTrue: [
+						| caseLabel |
+						caseLabel := (inLine findTokens: '	 :') second.
+						outLine := '	CASE(', caseLabel, ')' ].
+					inLine = '}' ifTrue: [
+						inPrimitiveResponse := false ] ].
+				] ] ] ].
+
+				outFileStream nextPutAll: outLine; cr.
+				extraOutLine ifNotNil: [
+					outFileStream nextPutAll: extraOutLine; cr ]]].
+
+	outFileStream close! !
+
+----QUIT----{31 December 2010 . 7:22:49 pm} VMMaker-Squeak4.1.image priorSource: 6098879!
+
+----STARTUP----{1 January 2011 . 11:54:57 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{1 January 2011 . 11:56:43 am} VMMaker-Squeak4.1.image priorSource: 6104104!
+
+----STARTUP----{1 January 2011 . 11:57:04 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 ].
+user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches]!
+
+"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 ].
+user = 'anon' ifTrue: [MCFileBasedRepository flushAllCaches]!
+
+----QUIT----{1 January 2011 . 12:01:07 pm} VMMaker-Squeak4.1.image priorSource: 6104104!
+
+----STARTUP----{1 January 2011 . 12:05:11 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{1 January 2011 . 12:13:36 pm} VMMaker-Squeak4.1.image priorSource: 6105162!
+
+----STARTUP----{1 January 2011 . 12:14:25 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{1 January 2011 . 12:15:18 pm} VMMaker-Squeak4.1.image priorSource: 6105162!
\ No newline at end of file

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

Modified: branches/Cog/image/Workspace.text
===================================================================
--- branches/Cog/image/Workspace.text	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/image/Workspace.text	2011-01-01 20:18:49 UTC (rev 2337)
@@ -4,10 +4,15 @@
 x86 platforms:
 	(VMMaker
 		generate: CoInterpreter
+		and: (Smalltalk
+				at: ([:choices| choices at: (UIManager default chooseFrom: choices)
+				ifAbsent: [^self]]
+					value: #(SimpleStackBasedCogit StackToRegisterMappingCogit)))
 		to: (FileDirectory default / '../src') fullName
 		platformDir: (FileDirectory default / '../platforms') fullName
-		excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin
-					FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin))
+		excluding:#(BrokenPlugin SlangTestPlugin TestOSAPlugin
+					FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin
+					NewsqueakIA32ABIPlugin NewsqueakIA32ABIPluginAttic))
 other platforms:
 	 (VMMaker
 		generate: StackInterpreter
Modified: branches/Cog/src/vm/cogit.c
===================================================================
--- branches/Cog/src/vm/cogit.c	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/src/vm/cogit.c	2011-01-01 20:18:49 UTC (rev 2337)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGenerator VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CCodeGenerator VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
    from
-	StackToRegisterMappingCogit VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	SimpleStackBasedCogit VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
  */
-static char __buildInfo[] = "StackToRegisterMappingCogit VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99 " __DATE__ ;
+static char __buildInfo[] = "SimpleStackBasedCogit VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c " __DATE__ ;
 char *__cogitBuildInfo = __buildInfo;
 
 
@@ -83,6 +83,14 @@
 
 
 typedef struct {
+	AbstractInstruction *targetInstruction;
+	sqInt	instructionIndex;
+ } BytecodeFixup;
+
+#define CogBytecodeFixup BytecodeFixup
+
+
+typedef struct {
 	sqInt	annotation;
 	AbstractInstruction *instruction;
  } InstructionAnnotation;
@@ -99,35 +107,7 @@
 #define CogPrimitiveDescriptor PrimitiveDescriptor
 
 
-typedef struct {
-	AbstractInstruction *targetInstruction;
-	sqInt	instructionIndex;
-	sqInt	simStackPtr;
-	sqInt	simSpillBase;
-	sqInt	mergeBase;
-	sqInt	optStatus;
- } BytecodeFixup;
 
-#define CogSSBytecodeFixup BytecodeFixup
-
-
-typedef struct {
-	char	type;
-	char	spilled;
-	sqInt	registerr;
-	sqInt	offset;
-	sqInt	constant;
-	sqInt	bcptr;
- } CogSimStackEntry;
-
-
-typedef struct {
-	sqInt	isReceiverResultRegLive;
-	CogSimStackEntry *ssEntry;
- } CogSSOptStatus;
-
-
-
 /*** Constants ***/
 #define AddCqR 82
 #define AddCwR 89
@@ -143,7 +123,6 @@
 #define ArithmeticShiftRightCqR 68
 #define ArithmeticShiftRightRR 69
 #define BaseHeaderSize 4
-#define BytesPerOop 4
 #define BytesPerWord 4
 #define Call 8
 #define CDQ 102
@@ -164,7 +143,6 @@
 #define CmpCwR 88
 #define CmpRdRd 95
 #define CmpRR 74
-#define ConstZero 1
 #define ConvertRRd 101
 #define CPUID 105
 #define Debug DEBUGVM
@@ -198,8 +176,6 @@
 #define FoxMFReceiver -12
 #define FoxThisContext -8
 #define FPReg -1
-#define GPRegMax -3
-#define GPRegMin -8
 #define HasBytecodePC 5
 #define HashBitsOffset 17
 #define HashMaskUnshifted 0xFFF
@@ -292,7 +268,7 @@
 #define NegateR 67
 #define Nop 7
 #define NumSendTrampolines 4
-#define NumTrampolines 50
+#define NumTrampolines 38
 #define OrCqR 85
 #define OrRR 78
 #define PopR 62
@@ -318,10 +294,6 @@
 #define SizeMask 0xFC
 #define SPReg -2
 #define SqrtRd 100
-#define SSBaseOffset 1
-#define SSConstant 2
-#define SSRegister 3
-#define SSSpill 4
 #define StackPointerIndex 2
 #define SubCqR 83
 #define SubCwR 90
@@ -376,7 +348,6 @@
 static AbstractInstruction * annotateobjRef(AbstractInstruction *abstractInstruction, sqInt anOop);
 static AbstractInstruction * annotatewith(AbstractInstruction *abstractInstruction, sqInt annotationFlag);
 static void assertSaneJumpTarget(void *jumpTarget);
-static sqInt availableRegisterOrNil(void);
 static sqInt blockCodeSize(unsigned char byteZero, unsigned char byteOne, unsigned char byteTwo, unsigned char byteThree);
 static sqInt blockDispatchTargetsForperformarg(CogMethod *cogMethod, usqInt (*binaryFunction)(sqInt mcpc, sqInt arg), sqInt arg);
 sqInt bytecodePCForstartBcpcin(sqInt mcpc, sqInt startbcpc, CogBlockMethod *cogMethod);
@@ -529,13 +500,8 @@
 static sqInt doubleExtendedDoAnythingBytecode(void);
 static sqInt duplicateTopBytecode(void);
 static BytecodeFixup * ensureFixupAt(sqInt targetIndex);
-static BytecodeFixup * ensureNonMergeFixupAt(sqInt targetIndex);
-static void ensureReceiverResultRegContainsSelf(void);
-static void ensureSpilledAtfrom(CogSimStackEntry * self_in_ensureSpilledAtfrom, sqInt baseOffset, sqInt baseRegister);
 void enterCogCodePopReceiver(void);
 void enterCogCodePopReceiverAndClassRegs(void);
-void enterCogCodePopReceiverArg0Regs(void);
-void enterCogCodePopReceiverArg1Arg0Regs(void);
 static sqInt extendedPushBytecode(void);
 static sqInt extendedStoreAndPopBytecode(void);
 static sqInt extendedStoreBytecode(void);
@@ -564,10 +530,8 @@
 static sqInt genDoubleArithmeticpreOpCheck(sqInt arithmeticOperator, AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg));
 static sqInt genDoubleComparisoninvert(AbstractInstruction *(*jumpOpcodeGenerator)(void *), sqInt invertComparison);
 static AbstractInstruction * genDoubleFailIfZeroArgRcvrarg(sqInt rcvrReg, sqInt argReg);
-static void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void) ;
 static void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void) ;
 static void (*genEnilopmartForcalled(sqInt regArg, char *trampolineName))(void) ;
-static void (*genEnterPICEnilopmartNumArgs(sqInt numArgs))(void) ;
 static sqInt genExtendedSendBytecode(void);
 static sqInt genExtendedSuperBytecode(void);
 static sqInt genExternalizePointersForPrimitiveCall(void);
@@ -625,16 +589,13 @@
 static sqInt genLongJumpIfTrue(void);
 static sqInt genLongUnconditionalBackwardJump(void);
 static sqInt genLongUnconditionalForwardJump(void);
-static sqInt genMarshalledSendSupernumArgs(sqInt selector, sqInt numArgs);
-static sqInt genMarshalledSendnumArgs(sqInt selector, sqInt numArgs);
-static sqInt genMethodAbortTrampolineFor(sqInt numArgs);
+static sqInt genMethodAbortTrampoline(void);
 static void genMulRR(AbstractInstruction * self_in_genMulRR, sqInt regSource, sqInt regDest);
 static sqInt genMustBeBooleanTrampolineForcalled(sqInt boolean, char *trampolineName);
 static sqInt genNonLocalReturnTrampoline(void);
 static sqInt genPassConstasArgument(AbstractInstruction * self_in_genPassConstasArgument, sqInt constant, sqInt zeroRelativeArgIndex);
 static sqInt genPassRegasArgument(AbstractInstruction * self_in_genPassRegasArgument, sqInt abstractRegister, sqInt zeroRelativeArgIndex);
-static sqInt genPICAbortTrampolineFor(sqInt numArgs);
-static sqInt genPICMissTrampolineFor(sqInt numArgs);
+static sqInt genPICAbortTrampoline(void);
 static sqInt genPopStackBytecode(void);
 static sqInt genPrimitiveAdd(void);
 static sqInt genPrimitiveAsFloat(void);
@@ -689,9 +650,6 @@
 static sqInt genPushReceiverBytecode(void);
 static sqInt genPushReceiverVariableBytecode(void);
 static sqInt genPushReceiverVariable(sqInt index);
-static void genPushRegisterArgs(void);
-static void genPushRegisterArgsForAbortMissNumArgs(sqInt numArgs);
-static void genPushRegisterArgsForNumArgs(sqInt numArgs);
 static sqInt genPushRemoteTempLongBytecode(void);
 static sqInt genPushTemporaryVariableBytecode(void);
 static sqInt genPushTemporaryVariable(sqInt index);
@@ -717,24 +675,19 @@
 static sqInt genSendLiteralSelector1ArgBytecode(void);
 static sqInt genSendLiteralSelector2ArgsBytecode(void);
 static sqInt genSendSupernumArgs(sqInt selector, sqInt numArgs);
-static sqInt genSendTrampolineFornumArgscalledargargargarg(void *aRoutine, sqInt numArgs, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt regOrConst2, sqInt regOrConst3);
 static sqInt genSendnumArgs(sqInt selector, sqInt numArgs);
 static sqInt genSetSmallIntegerTagsIn(sqInt scratchReg);
 static sqInt genShiftAwaySmallIntegerTagsInScratchReg(sqInt scratchReg);
 static sqInt genShortJumpIfFalse(void);
 static sqInt genShortUnconditionalJump(void);
 static sqInt genSmallIntegerComparison(sqInt jumpOpcode);
-static sqInt genSpecialSelectorArithmetic(void);
 static sqInt genSpecialSelectorClass(void);
-static sqInt genSpecialSelectorComparison(void);
 static sqInt genSpecialSelectorEqualsEquals(void);
 static sqInt genSpecialSelectorSend(void);
-static sqInt genSSPushSlotreg(sqInt index, sqInt baseReg);
 static sqInt genStoreAndPopReceiverVariableBytecode(void);
 static sqInt genStoreAndPopRemoteTempLongBytecode(void);
 static sqInt genStoreAndPopTemporaryVariableBytecode(void);
 static sqInt genStoreCheckTrampoline(void);
-static sqInt genStoreImmediateInSourceRegslotIndexdestReg(sqInt sourceReg, sqInt index, sqInt destReg);
 static sqInt genStorePopLiteralVariable(sqInt popBoolean, sqInt litVarIndex);
 static sqInt genStorePopMaybeContextReceiverVariable(sqInt popBoolean, sqInt slotIndex);
 static sqInt genStorePopReceiverVariable(sqInt popBoolean, sqInt slotIndex);
@@ -746,6 +699,8 @@
 static AbstractInstruction * genSubstituteReturnAddress(AbstractInstruction * self_in_genSubstituteReturnAddress, sqInt retpc);
 static sqInt genTrampolineForcalled(void *aRoutine, char *aString);
 static sqInt genTrampolineForcalledarg(void *aRoutine, char *aString, sqInt regOrConst0);
+static sqInt genTrampolineForcalledargarg(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1);
+static sqInt genTrampolineForcalledargargargarg(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt regOrConst2, sqInt regOrConst3);
 static sqInt genTrampolineForcalledargargargresult(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt regOrConst2, sqInt resultReg);
 static sqInt genTrampolineForcalledargargresult(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt resultReg);
 static sqInt genTrampolineForcalledargresult(void *aRoutine, char *aString, sqInt regOrConst0, sqInt resultReg);
@@ -771,14 +726,11 @@
 static BytecodeFixup * initializeFixupAt(sqInt targetIndex);
 static sqInt initialMethodUsageCount(void);
 static sqInt initialOpenPICUsageCount(void);
-static void initSimStackForFramefulMethod(sqInt startpc);
-static void initSimStackForFramelessMethod(sqInt startpc);
 static sqInt inlineCacheTagAt(AbstractInstruction * self_in_inlineCacheTagAt, sqInt callSiteReturnAddress);
 static sqInt inlineCacheTagForInstance(sqInt oop);
 static sqInt inlineCacheTagIsYoung(sqInt cacheTag);
 static sqInt instructionSizeAt(AbstractInstruction * self_in_instructionSizeAt, sqInt pc);
 sqInt interpretOffset(void);
-static sqInt inverseBranchFor(sqInt opcode);
 static sqInt isAFixup(AbstractInstruction * self_in_isAFixup, void *fixupOrAddress);
 static sqInt isAnInstruction(AbstractInstruction * self_in_isAnInstruction, void *addressOrInstruction);
 static sqInt isBigEndian(AbstractInstruction * self_in_isBigEndian);
@@ -789,7 +741,6 @@
 static sqInt isPCDependent(AbstractInstruction * self_in_isPCDependent);
 static sqInt isQuick(AbstractInstruction * self_in_isQuick, unsigned long operand);
 sqInt isSendReturnPC(sqInt retpc);
-static sqInt isSmallIntegerTagNonZero(void);
 static AbstractInstruction * gJumpAboveOrEqual(void *jumpTarget);
 static AbstractInstruction * gJumpAbove(void *jumpTarget);
 static AbstractInstruction * gJumpBelow(void *jumpTarget);
@@ -805,7 +756,6 @@
 static AbstractInstruction * gJumpLong(void *jumpTarget);
 static AbstractInstruction * gJumpNegative(void *jumpTarget);
 static AbstractInstruction * gJumpNonZero(void *jumpTarget);
-static AbstractInstruction * gJumpNoOverflow(void *jumpTarget);
 static AbstractInstruction * gJumpOverflow(void *jumpTarget);
 static AbstractInstruction * JumpRT(sqInt callTarget);
 static AbstractInstruction * gJumpR(sqInt reg);
@@ -827,7 +777,6 @@
 static sqInt leafCallStackPointerDelta(AbstractInstruction * self_in_leafCallStackPointerDelta);
 void linkSendAtintocheckedreceiver(sqInt callSiteReturnAddress, CogMethod *sendingMethod, CogMethod *targetMethod, sqInt checked, sqInt receiver);
 static sqInt literalBeforeFollowingAddress(AbstractInstruction * self_in_literalBeforeFollowingAddress, sqInt followingAddress);
-static sqInt liveRegisters(void);
 static sqInt loadLiteralByteSize(AbstractInstruction * self_in_loadLiteralByteSize);
 static sqInt longBranchDistance(unsigned char byteZero, unsigned char byteOne);
 static sqInt longForwardBranchDistance(unsigned char byteZero, unsigned char byteOne);
@@ -867,14 +816,11 @@
 void markMethodAndReferents(CogBlockMethod *aCogMethod);
 static void markYoungObjectsIn(CogMethod *cogMethod);
 static sqInt markYoungObjectspcmethod(sqInt annotation, char *mcpc, sqInt cogMethod);
-static void marshallSendArguments(sqInt numArgs);
 usqInt maxCogMethodAddress(void);
 static sqInt maybeFreeCogMethodDoesntLookKosher(CogMethod *cogMethod);
 static void maybeGenerateCheckFeatures(void);
 static void maybeGenerateICacheFlush(void);
 sqInt mcPCForstartBcpcin(sqInt bcpc, sqInt startbcpc, CogBlockMethod *cogMethod);
-static void mergeAtfrom(CogSimStackEntry * self_in_mergeAtfrom, sqInt baseOffset, sqInt baseRegister);
-static void mergeafterReturn(BytecodeFixup *fixup, sqInt mergeFollowsReturn);
 static sqInt methodAbortTrampolineFor(sqInt numArgs);
 static CogMethod * methodAfter(CogMethod *cogMethod);
 CogMethod * methodFor(void *address);
@@ -882,7 +828,6 @@
 sqInt mnuOffset(void);
 static sqInt modRMRO(AbstractInstruction * self_in_modRMRO, sqInt mod, sqInt regMode, sqInt regOpcode);
 static AbstractInstruction * gNegateR(sqInt reg);
-static AbstractInstruction * gNop(void);
 static sqInt nextBytecodePCForatbyte0in(BytecodeDescriptor *descriptor, sqInt pc, sqInt opcodeByte, sqInt aMethodObj);
 static sqInt nextBytecodePCInMapAfterininBlockupTo(sqInt startbcpc, sqInt methodObject, sqInt isInBlock, sqInt endpc);
 static sqInt noCogMethodsMaximallyMarked(void);
@@ -907,7 +852,6 @@
 sqInt pcisWithinMethod(char *address, CogMethod *cogMethod);
 static sqInt picAbortTrampolineFor(sqInt numArgs);
 static void planCompaction(void);
-static void popToReg(CogSimStackEntry * self_in_popToReg, sqInt reg);
 static PrimitiveDescriptor * primitiveGeneratorOrNil(void);
 void printCogMethodFor(void *address);
 void printCogMethods(void);
@@ -922,10 +866,7 @@
 void recordCallOffsetInof(CogMethod *cogMethod, void *callLabelArg);
 static void recordGeneratedRunTimeaddress(char *aString, sqInt address);
 sqInt recordPrimTraceFunc(void);
-static sqInt registerMask(CogSimStackEntry * self_in_registerMask);
-static sqInt registerMaskFor(sqInt reg);
 static sqInt registerMaskForandand(sqInt reg1, sqInt reg2, sqInt reg3);
-static sqInt registerOrNil(CogSimStackEntry * self_in_registerOrNil);
 static void relocateAndPruneYoungReferrers(void);
 static void relocateCallBeforeReturnPCby(AbstractInstruction * self_in_relocateCallBeforeReturnPCby, sqInt retpc, sqInt delta);
 static void relocateCallsAndSelfReferencesInMethod(CogMethod *cogMethod);
@@ -965,31 +906,10 @@
 static sqInt sizePCDependentInstructionAt(AbstractInstruction * self_in_sizePCDependentInstructionAt, sqInt eventualAbsoluteAddress);
 static sqInt slotOffsetOfInstVarIndex(sqInt index);
 static sqInt spanForatbyte0in(BytecodeDescriptor *descriptor, sqInt pc, sqInt opcodeByte, sqInt aMethodObj);
-static void ssAllocateCallReg(sqInt requiredReg1);
-static void ssAllocateCallRegand(sqInt requiredReg1, sqInt requiredReg2);
-static sqInt ssAllocatePreferredReg(sqInt preferredReg);
-static void ssAllocateRequiredRegMaskupThrough(sqInt requiredRegsMask, sqInt stackPtr);
-static void ssAllocateRequiredReg(sqInt requiredReg);
-static void ssAllocateRequiredRegand(sqInt requiredReg1, sqInt requiredReg2);
-static void ssAllocateRequiredRegupThrough(sqInt requiredReg, sqInt stackPtr);
-static void ssFlushTo(sqInt index);
-static void ssFlushUpThroughReceiverVariable(sqInt slotIndex);
-static void ssFlushUpThroughTemporaryVariable(sqInt tempIndex);
-static void ssPop(sqInt n);
-static sqInt ssPushBaseoffset(sqInt reg, sqInt offset);
-static sqInt ssPushConstant(sqInt literal);
-static sqInt ssPushDesc(CogSimStackEntry simStackEntry);
-static sqInt ssPushRegister(sqInt reg);
-static void ssPush(sqInt n);
-static sqInt ssStorePoptoPreferredReg(sqInt popBoolean, sqInt preferredReg);
-static CogSimStackEntry * ssTop(void);
-static CogSimStackEntry ssTopDescriptor(void);
-static CogSimStackEntry * ssValue(sqInt n);
 static sqInt stackBytesForNumArgs(AbstractInstruction * self_in_stackBytesForNumArgs, sqInt numArgs);
 sqInt stackPageHeadroomBytes(void);
 static sqInt stackPageInterruptHeadroomBytes(AbstractInstruction * self_in_stackPageInterruptHeadroomBytes);
 static void storeLiteralbeforeFollowingAddress(AbstractInstruction * self_in_storeLiteralbeforeFollowingAddress, sqInt literal, sqInt followingAddress);
-static void storeToReg(CogSimStackEntry * self_in_storeToReg, sqInt reg);
 static sqInt sib(AbstractInstruction * self_in_sib, sqInt scale, sqInt indexReg, sqInt baseReg);
 sqInt traceLinkedSendOffset(void);
 static char * trampolineNamenumArgs(char *routinePrefix, sqInt numArgs);
@@ -1036,7 +956,6 @@
 static sqInt bytecodePointer;
 void * CFramePointer;
 void * CStackPointer;
-static sqInt callerSavedRegMask;
 sqInt ceBaseFrameReturnTrampoline;
 sqInt ceCannotResumeTrampoline;
 void (*ceCaptureCStackPointers)(void);
@@ -1045,12 +964,7 @@
 static sqInt ceClosureCopyTrampoline;
 static sqInt ceCPICMissTrampoline;
 static sqInt ceCreateNewArrayTrampoline;
-void (*ceEnter0ArgsPIC)(void);
-void (*ceEnter1ArgsPIC)(void);
-void (*ceEnter2ArgsPIC)(void);
 void (*ceEnterCogCodePopReceiverAndClassRegs)(void);
-void (*ceEnterCogCodePopReceiverArg0Regs)(void);
-void (*ceEnterCogCodePopReceiverArg1Arg0Regs)(void);
 void (*ceEnterCogCodePopReceiverReg)(void);
 static sqInt ceFetchContextInstVarTrampoline;
 static void (*ceFlushICache)(unsigned long from, unsigned long to);
@@ -1083,7 +997,6 @@
 static sqInt cPICCaseSize;
 static sqInt cPICEndSize;
 static const int cStackAlignment = STACK_ALIGN_BYTES;
-static sqInt debugFixupBreaks;
 unsigned long debugPrimCallStackOffset;
 static AbstractInstruction * endCPICCase0;
 static AbstractInstruction * endCPICCase1;
@@ -1098,22 +1011,22 @@
 static sqInt firstSend;
 static BytecodeFixup * fixups;
 static BytecodeDescriptor generatorTable[256] = {
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
@@ -1210,7 +1123,7 @@
 	{ genStoreAndPopTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genStoreAndPopTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genStoreAndPopTemporaryVariableBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
-	{ genPushReceiverBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
+	{ genPushReceiverBytecode, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushConstantTrueBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushConstantFalseBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genPushConstantNilBytecode, (sqInt (*)(unsigned char,...))0, 1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
@@ -1274,28 +1187,28 @@
 	{ genLongJumpIfFalse, (sqInt (*)(unsigned char,...))longForwardBranchDistance, 0, 0, 2, 1, 1, 1, 0, 0, 1, 0, 0, 1, 0 },
 	{ genLongJumpIfFalse, (sqInt (*)(unsigned char,...))longForwardBranchDistance, 0, 0, 2, 1, 1, 1, 0, 0, 1, 0, 0, 1, 0 },
 	{ genLongJumpIfFalse, (sqInt (*)(unsigned char,...))longForwardBranchDistance, 0, 0, 2, 1, 1, 1, 0, 0, 1, 0, 0, 1, 0 },
-	{ genSpecialSelectorArithmetic, (sqInt (*)(unsigned char,...))0, 0, 75, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorArithmetic, (sqInt (*)(unsigned char,...))0, 0, 76, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 23, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 25, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 26, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 24, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 15, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorComparison, (sqInt (*)(unsigned char,...))0, 0, 16, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorArithmetic, (sqInt (*)(unsigned char,...))0, 0, 77, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
-	{ genSpecialSelectorArithmetic, (sqInt (*)(unsigned char,...))0, 0, 78, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
+	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
 	{ genSpecialSelectorEqualsEquals, (sqInt (*)(unsigned char,...))0, -1, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genSpecialSelectorClass, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 },
 	{ genSpecialSelectorSend, (sqInt (*)(unsigned char,...))0, 0, 0, 1, 1, 1, 0, 0, 0, 0, 0, 0, 1, 0 },
@@ -1364,12 +1277,10 @@
 static sqInt lastSend;
 static usqInt limitAddress;
 static CogBlockMethod * maxMethodBefore;
-static sqInt methodAbortTrampolines[4];
 static sqInt methodBytesFreedSinceLastCompaction;
 static AbstractInstruction *methodLabel = &aMethodLabel;
 static sqInt methodObj;
 static sqInt methodOrBlockNumArgs;
-static sqInt methodOrBlockNumTemps;
 static sqInt methodZoneBase;
 static sqInt missOffset;
 static AbstractInstruction * mnuCall;
@@ -1381,9 +1292,6 @@
 static sqInt opcodeIndex;
 static CogMethod *openPICList = 0;
 static sqInt openPICSize;
-static CogSSOptStatus optStatus;
-static sqInt picAbortTrampolines[4];
-static sqInt picMissTrampolines[4];
 static void (*postCompileHook)(CogMethod *, void *);
 static AbstractInstruction * primInvokeLabel;
 static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1] = {
@@ -1613,16 +1521,9 @@
 };
 static sqInt primitiveIndex;
 void (*realCEEnterCogCodePopReceiverAndClassRegs)(void);
-void (*realCEEnterCogCodePopReceiverArg0Regs)(void);
-void (*realCEEnterCogCodePopReceiverArg1Arg0Regs)(void);
 void (*realCEEnterCogCodePopReceiverReg)(void);
-static sqInt regArgsHaveBeenPushed;
 static AbstractInstruction * sendMissCall;
 static sqInt sendTrampolines[NumSendTrampolines];
-static CogSimStackEntry simSelf;
-static sqInt simSpillBase;
-static CogSimStackEntry simStack[256];
-static sqInt simStackPtr;
 static AbstractInstruction * stackCheckLabel;
 static AbstractInstruction * stackOverflowCall;
 static sqInt superSendTrampolines[NumSendTrampolines];
@@ -1675,7 +1576,7 @@
 #define noCheckEntryOffset() cmNoCheckEntryOffset
 #define noContextSwitchBlockEntryOffset() blockNoContextSwitchOffset
 #define notYetImplemented() warning("not yet implemented")
-#define numRegArgs() 1
+#define numRegArgs() 0
 #define printNum(n) printf("%ld", (long) n)
 #define printOnTrace() (traceLinkedSends & 8)
 #define print(aString) printf(aString)
@@ -1685,12 +1586,7 @@
 #define reportError(n) warning("compilation error")
 #define setCFramePointer(theFP) (CFramePointer = (void *)(theFP))
 #define setCStackPointer(theSP) (CStackPointer = (void *)(theSP))
-#define simStackAt(index) (simStack + (index))
-#define traceDescriptor(ign) 0
-#define traceFixup(ign) 0
 #define traceMapbyteatfor(ig,no,re,d) 0
-#define traceMerge(ign) 0
-#define traceSimStack() 0
 #define tryLockVMOwner() (ceTryLockVMOwner() != 0)
 #define typeEtAlWord(cm) (((long *)(cm))[1])
 #define unlockVMOwner() ceUnlockVMOwner()
@@ -2036,30 +1932,6 @@
 }
 
 static sqInt
-availableRegisterOrNil(void)
-{
-    sqInt liveRegs;
-
-	liveRegs = liveRegisters();
-	if (!(liveRegs & (registerMaskFor(Arg1Reg)))) {
-		return Arg1Reg;
-	}
-	if (!(liveRegs & (registerMaskFor(Arg0Reg)))) {
-		return Arg0Reg;
-	}
-	if (!(liveRegs & (registerMaskFor(SendNumArgsReg)))) {
-		return SendNumArgsReg;
-	}
-	if (!(liveRegs & (registerMaskFor(ClassReg)))) {
-		return ClassReg;
-	}
-	if (!(liveRegs & (registerMaskFor(ReceiverResultReg)))) {
-		return ReceiverResultReg;
-	}
-	return null;
-}
-
-static sqInt
 blockCodeSize(unsigned char byteZero, unsigned char byteOne, unsigned char byteTwo, unsigned char byteThree)
 {
 	return (byteTwo * 256) + byteThree;
@@ -2113,7 +1985,9 @@
 sqInt
 bytecodePCForstartBcpcin(sqInt mcpc, sqInt startbcpc, CogBlockMethod *cogMethod)
 {
-	if (mcpc == ((((sqInt)cogMethod)) + ((cogMethod->stackCheckOffset)))) {
+	if (mcpc == ((((cogMethod->stackCheckOffset)) == 0
+	? (((sqInt)cogMethod)) + (sizeof(CogBlockMethod))
+	: (((sqInt)cogMethod)) + ((cogMethod->stackCheckOffset))))) {
 		return startbcpc;
 	}
 	return mapForbcpcperformUntilarg(cogMethod, startbcpc, findMcpcBcpcMatchingMcpc, ((void *) mcpc));
@@ -3123,34 +2997,13 @@
 static sqInt
 compileAbstractInstructionsFromthrough(sqInt start, sqInt end)
 {
-    sqInt deadCode;
-    sqInt debugBytecodePointers;
     BytecodeDescriptor *descriptor;
     BytecodeFixup *fixup;
     sqInt nextOpcodeIndex;
     sqInt result;
 
-	traceSimStack();
 	bytecodePointer = start;
-	descriptor = null;
-	deadCode = 0;
 	do {
-		;
-		fixup = fixupAt(bytecodePointer - initialPC);
-		if ((((usqInt)((fixup->targetInstruction)))) > 0) {
-			deadCode = 0;
-			if ((((usqInt)((fixup->targetInstruction)))) >= 2) {
-				mergeafterReturn(fixup, (descriptor != null)
-				 && ((descriptor->isReturn)));
-			}
-		}
-		else {
-			if ((descriptor != null)
-			 && ((descriptor->isReturn))) {
-				deadCode = 1;
-			}
-		}
-		;
 		byte0 = fetchByteofObject(bytecodePointer, methodObj);
 		descriptor = generatorAt(byte0);
 		if (((descriptor->numBytes)) > 1) {
@@ -3166,16 +3019,9 @@
 			}
 		}
 		nextOpcodeIndex = opcodeIndex;
-		result = (deadCode
-			? (((descriptor->isMapped))
- || (inBlock
- && ((descriptor->isMappedInBlock)))
-	? annotateBytecode(gNop())
-	: 0),0
-			: ((descriptor->generator))());
-		traceDescriptor(descriptor);
-		traceSimStack();
-		if ((((((usqInt)((fixup->targetInstruction)))) >= 1) && ((((usqInt)((fixup->targetInstruction)))) <= 2))) {
+		result = ((descriptor->generator))();
+		fixup = fixupAt(bytecodePointer - initialPC);
+		if (((fixup->targetInstruction)) != 0) {
 			if (opcodeIndex == nextOpcodeIndex) {
 				gLabel();
 			}
@@ -3272,18 +3118,12 @@
 	sp->	Nth temp
 	Avoid use of SendNumArgsReg which is the flag determining whether
 	context switch is allowed on stack-overflow. */
-/*	Build a frame for a block activation. See CoInterpreter
-	class>>initializeFrameIndices. Override to push the register receiver and
-	register arguments, if any, and to correctly
-	initialize the explicitly nilled/pushed temp entries (they are /not/ of
-	type constant nil). */
 
 static void
 compileBlockFrameBuild(BlockStart *blockStart)
 {
     AbstractInstruction * cascade0;
     sqInt i;
-    sqInt ign;
 
 	annotateBytecode(gLabel());
 	gPushR(FPReg);
@@ -3304,33 +3144,19 @@
 	gCmpRR(TempReg, SPReg);
 	gJumpBelow(stackOverflowCall);
 	(blockStart->stackCheckLabel = annotateBytecode(gLabel()));
-	methodOrBlockNumTemps = (((blockStart->numArgs)) + ((blockStart->numCopied))) + ((blockStart->numInitialNils));
-	initSimStackForFramefulMethod((blockStart->startpc));
-	if (((blockStart->numInitialNils)) > 0) {
-		if (((blockStart->numInitialNils)) > 1) {
-			annotateobjRef(gMoveCwR(nilObject(), TempReg), nilObject());
-			for (ign = 1; ign <= ((blockStart->numInitialNils)); ign += 1) {
-				gPushR(TempReg);
-			}
-		}
-		else {
-			annotateobjRef(gPushCw(nilObject()), nilObject());
-		}
-		methodOrBlockNumTemps = ((blockStart->numArgs)) + ((blockStart->numCopied));
-	}
 }
 
 
-/*	Make sure ReceiverResultReg holds the receiver, loaded from
-	the closure, which is what is initially in ReceiverResultReg */
-/*	Make sure ReceiverResultReg holds the receiver, loaded from
-	the closure, which is what is initially in ReceiverResultReg */
+/*	Make sure ReceiverResultReg holds the receiver, loaded from the closure,
+	which is what is initially in ReceiverResultReg. We must annotate the
+	first instruction so that findMethodForStartBcpc:inHomeMethod: can
+	function. We need two annotations because the first is a fiducial. */
 
 static void
 compileBlockFramelessEntry(BlockStart *blockStart)
 {
-	methodOrBlockNumTemps = ((blockStart->numArgs)) + ((blockStart->numCopied));
-	initSimStackForFramelessMethod((blockStart->startpc));
+	annotateBytecode((blockStart->entryLabel));
+	annotateBytecode((blockStart->entryLabel));
 	genLoadSlotsourceRegdestReg(ClosureOuterContextIndex, ReceiverResultReg, TempReg);
 	genLoadSlotsourceRegdestReg(ReceiverIndex, TempReg, ReceiverResultReg);
 }
@@ -3369,14 +3195,11 @@
 static CogMethod *
 compileCogMethod(sqInt selector)
 {
-    sqInt debugStackPointers;
     sqInt extra;
     sqInt numBlocks;
     sqInt numBytecodes;
     sqInt result;
 
-	methodOrBlockNumTemps = tempCountOf(methodObj);
-	;
 	hasYoungReferent = (isYoung(methodObj))
 	 || (isYoung(selector));
 	methodOrBlockNumArgs = argumentCountOf(methodObj);
@@ -3497,9 +3320,6 @@
 	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
 	it is the flag determining whether context switch is allowed on
 	stack-overflow.  */
-/*	Build a frame for a CogMethod activation. See CoInterpreter
-	class>>initializeFrameIndices. Override to push the register receiver and
-	register arguments, if any. */
 
 static void
 compileFrameBuild(void)
@@ -3508,13 +3328,8 @@
     AbstractInstruction *jumpSkip;
 
 	if (!(needsFrame)) {
-		initSimStackForFramelessMethod(initialPC);
 		return;
 	}
-	genPushRegisterArgs();
-	if (!(needsFrame)) {
-		return;
-	}
 	gPushR(FPReg);
 	gMoveRR(SPReg, FPReg);
 	addDependent(methodLabel, annotateMethodRef(gPushCw(((sqInt)methodLabel))));
@@ -3541,7 +3356,6 @@
 		jmpTarget(jumpSkip, stackCheckLabel = gLabel());
 	}
 	annotateBytecode(stackCheckLabel);
-	initSimStackForFramefulMethod(initialPC);
 }
 
 
@@ -3698,14 +3512,12 @@
 
 
 /*	Compile the abstract instructions for the entire method. */
-/*	Compile the abstract instructions for a method. */
 
 static sqInt
 compileMethod(void)
 {
     sqInt result;
 
-	regArgsHaveBeenPushed = 0;
 	compileProlog();
 	compileEntry();
 	if (((result = compilePrimitive())) < 0) {
@@ -3747,7 +3559,7 @@
 	while (compiledBlocksCount < blockCount) {
 		blockStart = blockStartAt(compiledBlocksCount);
 		compileBlockEntry(blockStart);
-		if (((result = compileAbstractInstructionsFromthrough(((blockStart->startpc)) + ((blockStart->numInitialNils)), (((blockStart->startpc)) + ((blockStart->span))) - 1))) < 0) {
+		if (((result = compileAbstractInstructionsFromthrough((blockStart->startpc), (((blockStart->startpc)) + ((blockStart->span))) - 1))) < 0) {
 			return result;
 		}
 		compiledBlocksCount += 1;
@@ -3780,7 +3592,7 @@
 
 /*	Compile the code for an open PIC. Perform a probe of the first-level
 	method lookup cache followed by a call of ceSendFromOpenPIC: if the probe
-	fails. Override to push the register args when calling ceSendFromOpenPIC: */
+	fails.  */
 
 static void
 compileOpenPICnumArgs(sqInt selector, sqInt numArgs)
@@ -3842,7 +3654,6 @@
 	gCmpRR(SendNumArgsReg, TempReg);
 	gJumpZero(itsAHit);
 	jmpTarget(jumpSelectorMiss, gLabel());
-	genPushRegisterArgsForNumArgs(numArgs);
 	genSaveStackPointers();
 	genLoadCStackPointers();
 	addDependent(methodLabel, annotateMethodRef(gMoveCwR(((sqInt)methodLabel), SendNumArgsReg)));
@@ -6140,7 +5951,7 @@
 static sqInt
 cPICMissTrampolineFor(sqInt numArgs)
 {
-	return picMissTrampolines[((numArgs < ((numRegArgs()) + 1)) ? numArgs : ((numRegArgs()) + 1))];
+	return ceCPICMissTrampoline;
 }
 
 static sqInt
@@ -6532,10 +6343,9 @@
 static sqInt
 duplicateTopBytecode(void)
 {
-    CogSimStackEntry desc;
-
-	desc = ssTopDescriptor();
-	return ssPushDesc(desc);
+	gMoveMwrR(0, SPReg, TempReg);
+	gPushR(TempReg);
+	return 0;
 }
 
 
@@ -6550,93 +6360,13 @@
     BytecodeFixup *fixup;
 
 	fixup = fixupAt(targetIndex);
-	traceFixup(fixup);
-	;
-	if ((((usqInt)((fixup->targetInstruction)))) <= 1) {
-		(fixup->targetInstruction = ((AbstractInstruction *) 2));
-		(fixup->simStackPtr = simStackPtr);
-	}
-	else {
-		if (((fixup->simStackPtr)) <= -2) {
-			(fixup->simStackPtr = simStackPtr);
-		}
-		else {
-			assert(((fixup->simStackPtr)) == simStackPtr);
-		}
-	}
-	return fixup;
-}
-
-
-/*	Make sure there's a flagged fixup at the targetIndex (pc relative to first
-	pc) in fixups.
-	Initially a fixup's target is just a flag. Later on it is replaced with a
-	proper instruction. */
-
-static BytecodeFixup *
-ensureNonMergeFixupAt(sqInt targetIndex)
-{
-    BytecodeFixup *fixup;
-
-	fixup = fixupAt(targetIndex);
 	if (((fixup->targetInstruction)) == 0) {
 		(fixup->targetInstruction = ((AbstractInstruction *) 1));
 	}
-	;
 	return fixup;
 }
 
-static void
-ensureReceiverResultRegContainsSelf(void)
-{
-	if (needsFrame) {
-		if (!(((optStatus.isReceiverResultRegLive))
-			 && (((optStatus.ssEntry)) == ((&simSelf))))) {
-			ssAllocateRequiredReg(ReceiverResultReg);
-			storeToReg((&simSelf), ReceiverResultReg);
-		}
-		(optStatus.isReceiverResultRegLive = 1);
-		(optStatus.ssEntry = (&simSelf));
-	}
-	else {
-		assert((((simSelf.type)) == SSRegister)
-		 && (((simSelf.registerr)) == ReceiverResultReg));
-		assert(((optStatus.isReceiverResultRegLive))
-		 && (((optStatus.ssEntry)) == ((&simSelf))));
-	}
-}
 
-static void
-ensureSpilledAtfrom(CogSimStackEntry * self_in_ensureSpilledAtfrom, sqInt baseOffset, sqInt baseRegister)
-{
-	if ((self_in_ensureSpilledAtfrom->spilled)) {
-		if (((self_in_ensureSpilledAtfrom->type)) == SSSpill) {
-			assert((((self_in_ensureSpilledAtfrom->offset)) == baseOffset)
-			 && (((self_in_ensureSpilledAtfrom->registerr)) == baseRegister));
-			return;
-		}
-	}
-	assert(((self_in_ensureSpilledAtfrom->type)) != SSSpill);
-	if (((self_in_ensureSpilledAtfrom->type)) == SSConstant) {
-		annotateobjRef(gPushCw((self_in_ensureSpilledAtfrom->constant)), (self_in_ensureSpilledAtfrom->constant));
-	}
-	else {
-		if (((self_in_ensureSpilledAtfrom->type)) == SSBaseOffset) {
-			gMoveMwrR((self_in_ensureSpilledAtfrom->offset), (self_in_ensureSpilledAtfrom->registerr), TempReg);
-			gPushR(TempReg);
-		}
-		else {
-			assert(((self_in_ensureSpilledAtfrom->type)) == SSRegister);
-			gPushR((self_in_ensureSpilledAtfrom->registerr));
-		}
-		(self_in_ensureSpilledAtfrom->type) = SSSpill;
-		(self_in_ensureSpilledAtfrom->offset) = baseOffset;
-		(self_in_ensureSpilledAtfrom->registerr) = baseRegister;
-	}
-	(self_in_ensureSpilledAtfrom->spilled) = 1;
-}
-
-
 /*	This is a static version of ceEnterCogCodePopReceiverReg
 	for break-pointing when debugging in C. */
 /*	(and this exists only to reference Debug) */
@@ -6664,34 +6394,6 @@
 	realCEEnterCogCodePopReceiverAndClassRegs();
 }
 
-
-/*	This is a static version of ceEnterCogCodePopReceiverArg0Regs
-	for break-pointing when debugging in C. */
-/*	(and this exists only to reference Debug) */
-
-void
-enterCogCodePopReceiverArg0Regs(void)
-{
-	if (!(Debug)) {
-		error("what??");
-	}
-	realCEEnterCogCodePopReceiverArg0Regs();
-}
-
-
-/*	This is a static version of ceEnterCogCodePopReceiverArg1Arg0Regs
-	for break-pointing when debugging in C. */
-/*	(and this exists only to reference Debug) */
-
-void
-enterCogCodePopReceiverArg1Arg0Regs(void)
-{
-	if (!(Debug)) {
-		error("what??");
-	}
-	realCEEnterCogCodePopReceiverArg1Arg0Regs();
-}
-
 static sqInt
 extendedPushBytecode(void)
 {
@@ -6842,11 +6544,13 @@
 findBlockMethodWithStartMcpcbcpc(sqInt blockEntryPC, sqInt startBcpc)
 {
     CogBlockMethod *cogBlockMethod;
-    sqInt stackCheckMcpc;
+    sqInt startMcpc;
 
 	cogBlockMethod = ((CogBlockMethod *) (blockEntryPC - (sizeof(CogBlockMethod))));
-	stackCheckMcpc = (((usqInt)cogBlockMethod)) + ((cogBlockMethod->stackCheckOffset));
-	if ((bytecodePCForstartBcpcin(stackCheckMcpc, startBcpc, cogBlockMethod)) == startBcpc) {
+	startMcpc = (((cogBlockMethod->stackCheckOffset)) == 0
+		? cogBlockMethod
+		: (((usqInt)cogBlockMethod)) + ((cogBlockMethod->stackCheckOffset)));
+	if ((bytecodePCForstartBcpcin(startMcpc, startBcpc, cogBlockMethod)) == startBcpc) {
 		return ((usqInt)cogBlockMethod);
 	}
 	return 0;
@@ -6899,8 +6603,10 @@
 
 /*	Find the CMMethod or CMBlock that has zero-relative startbcpc as its first
 	bytecode pc.
-	As this is for cannot resme processing it doesn't have to be fast.
-	Enumerate block returns and map to bytecode pcs */
+	As this is for cannot resume processing and/or conversion to machine-code
+	on backward
+	branch, it doesn't have to be fast. Enumerate block returns and map to
+	bytecode pcs. */
 
 CogBlockMethod *
 findMethodForStartBcpcinHomeMethod(sqInt startbcpc, CogMethod *cogMethod)
@@ -7229,27 +6935,29 @@
 }
 
 
-/*	Receiver and arg in registers.
-	Stack looks like
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
 	return address */
 
 static sqInt
 genDoubleArithmeticpreOpCheck(sqInt arithmeticOperator, AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg))
 {
     AbstractInstruction *doOp;
+    AbstractInstruction *fail;
     AbstractInstruction *jumpFailAlloc;
     AbstractInstruction *jumpFailCheck;
     AbstractInstruction *jumpFailClass;
     AbstractInstruction *jumpSmallInt;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
 	genGetDoubleValueOfinto(ReceiverResultReg, DPFPReg0);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpSmallInt = genJumpSmallIntegerInScratchReg(TempReg);
-	genGetCompactClassIndexNonIntOfinto(Arg0Reg, SendNumArgsReg);
+	genGetCompactClassIndexNonIntOfinto(ClassReg, SendNumArgsReg);
 	gCmpCqR(classFloatCompactIndex(), SendNumArgsReg);
 	jumpFailClass = gJumpNonZero(0);
-	genGetDoubleValueOfinto(Arg0Reg, DPFPReg1);
+	genGetDoubleValueOfinto(ClassReg, DPFPReg1);
 	doOp = gLabel();
 	if (preOpCheckOrNil == null) {
 		null;
@@ -7260,30 +6968,29 @@
 	genoperandoperand(arithmeticOperator, DPFPReg1, DPFPReg0);
 	jumpFailAlloc = genAllocFloatValueintoscratchRegscratchReg(DPFPReg0, SendNumArgsReg, ClassReg, TempReg);
 	gMoveRR(SendNumArgsReg, ReceiverResultReg);
-	gRetN(0);
-	assert(methodOrBlockNumArgs <= (numRegArgs()));
-	jmpTarget(jumpFailClass, gLabel());
-	if (preOpCheckOrNil == null) {
-		null;
-	}
-	else {
-		jmpTarget(jumpFailCheck, getJmpTarget(jumpFailClass));
-	}
-	genPushRegisterArgsForNumArgs(methodOrBlockNumArgs);
-	jumpFailClass = gJump(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpSmallInt, gLabel());
 	genConvertSmallIntegerToIntegerInScratchReg(ClassReg);
 	gConvertRRd(ClassReg, DPFPReg1);
 	gJump(doOp);
 	jmpTarget(jumpFailAlloc, gLabel());
 	compileInterpreterPrimitive(functionPointerForCompiledMethodprimitiveIndex(methodObj, primitiveIndex));
+	fail = gLabel();
 	jmpTarget(jumpFailClass, gLabel());
+	if (preOpCheckOrNil == null) {
+		null;
+	}
+	else {
+		jmpTarget(jumpFailCheck, fail);
+	}
 	return 0;
 }
 
 
-/*	Receiver and arg in registers.
-	Stack looks like
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
 	return address */
 
 static sqInt
@@ -7294,13 +7001,14 @@
     AbstractInstruction *jumpFail;
     AbstractInstruction *jumpSmallInt;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
 	genGetDoubleValueOfinto(ReceiverResultReg, DPFPReg0);
+	gMoveRR(TempReg, ClassReg);
 	jumpSmallInt = genJumpSmallIntegerInScratchReg(TempReg);
-	genGetCompactClassIndexNonIntOfinto(Arg0Reg, SendNumArgsReg);
+	genGetCompactClassIndexNonIntOfinto(ClassReg, SendNumArgsReg);
 	gCmpCqR(classFloatCompactIndex(), SendNumArgsReg);
 	jumpFail = gJumpNonZero(0);
-	genGetDoubleValueOfinto(Arg0Reg, DPFPReg1);
+	genGetDoubleValueOfinto(ClassReg, DPFPReg1);
 	if (invertComparison) {
 
 		/* May need to invert for NaNs */
@@ -7315,12 +7023,13 @@
 
 	jumpCond = jumpOpcodeGenerator(0);
 	annotateobjRef(gMoveCwR(falseObject(), ReceiverResultReg), falseObject());
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpCond, annotateobjRef(gMoveCwR(trueObject(), ReceiverResultReg), trueObject()));
-	gRetN(0);
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpSmallInt, gLabel());
-	genConvertSmallIntegerToIntegerInScratchReg(Arg0Reg);
-	gConvertRRd(Arg0Reg, DPFPReg1);
+	genConvertSmallIntegerToIntegerInScratchReg(ClassReg);
+	gConvertRRd(ClassReg, DPFPReg1);
 	gJump(compare);
 	jmpTarget(jumpFail, gLabel());
 	return 0;
@@ -7343,38 +7052,6 @@
 	then executes a return instruction to pop off the entry-point and jump to
 	it.  */
 
-static void (*genEnilopmartForandandcalled(sqInt regArg1, sqInt regArg2, sqInt regArg3, char *trampolineName))(void)
-
-{
-    sqInt endAddress;
-    sqInt enilopmart;
-    sqInt size;
-
-	opcodeIndex = 0;
-	genLoadStackPointers();
-	gPopR(regArg3);
-	gPopR(regArg2);
-	gPopR(regArg1);
-	gRetN(0);
-	computeMaximumSizes();
-	size = generateInstructionsAt(methodZoneBase);
-	endAddress = outputInstructionsAt(methodZoneBase);
-	assert((methodZoneBase + size) == endAddress);
-	enilopmart = methodZoneBase;
-	methodZoneBase = alignUptoRoutineBoundary(endAddress);
-	nopsFromto(backEnd, endAddress, methodZoneBase - 1);
-	recordGeneratedRunTimeaddress(trampolineName, enilopmart);
-	return ((void (*)(void)) enilopmart);
-}
-
-
-/*	An enilopmart (the reverse of a trampoline) is a piece of code that makes
-	the system-call-like transition from the C runtime into generated machine
-	code. The desired arguments and entry-point are pushed on a stackPage's
-	stack. The enilopmart pops off the values to be loaded into registers and
-	then executes a return instruction to pop off the entry-point and jump to
-	it.  */
-
 static void (*genEnilopmartForandcalled(sqInt regArg1, sqInt regArg2, char *trampolineName))(void)
 
 {
@@ -7429,44 +7106,6 @@
 }
 
 
-/*	Generate special versions of the ceEnterCogCodePopReceiverAndClassRegs
-	enilopmart that also pop register args from the stack to undo the pushing
-	of register args in the abort/miss trampolines. */
-
-static void (*genEnterPICEnilopmartNumArgs(sqInt numArgs))(void)
-
-{
-    sqInt endAddress;
-    sqInt enilopmart;
-    sqInt size;
-
-	opcodeIndex = 0;
-	genLoadStackPointers();
-	gPopR(ClassReg);
-	gPopR(TempReg);
-	gPopR(SendNumArgsReg);
-	if (numArgs > 0) {
-		if (numArgs > 1) {
-			gPopR(Arg1Reg);
-			assert((numRegArgs()) == 2);
-		}
-		gPopR(Arg0Reg);
-	}
-	gPopR(ReceiverResultReg);
-	gPushR(SendNumArgsReg);
-	gJumpR(TempReg);
-	computeMaximumSizes();
-	size = generateInstructionsAt(methodZoneBase);
-	endAddress = outputInstructionsAt(methodZoneBase);
-	assert((methodZoneBase + size) == endAddress);
-	enilopmart = methodZoneBase;
-	methodZoneBase = alignUptoRoutineBoundary(endAddress);
-	nopsFromto(backEnd, endAddress, methodZoneBase - 1);
-	recordGeneratedRunTimeaddress(trampolineNamenumArgs("ceEnterPIC", numArgs), enilopmart);
-	return ((void (*)(void)) enilopmart);
-}
-
-
 /*	Can use any of the first 32 literals for the selector and pass up to 7
 	arguments. 
  */
@@ -7483,13 +7122,9 @@
 	return genSendSupernumArgs(literalofMethod(byte1 & 31, methodObj), ((usqInt) byte1) >> 5);
 }
 
-
-/*	Override to push the register receiver and register arguments, if any. */
-
 static sqInt
 genExternalizePointersForPrimitiveCall(void)
 {
-	genPushRegisterArgs();
 	gMoveMwrR(0, SPReg, ClassReg);
 	gMoveRAw(FPReg, framePointerAddress());
 	gLoadEffectiveAddressMwrR(BytesPerWord, SPReg, TempReg);
@@ -7673,9 +7308,6 @@
 /*	Enilopmarts transfer control from C into machine code (backwards
 	trampolines). 
  */
-/*	Enilopmarts transfer control from C into machine code (backwards
-	trampolines). Override to add version for generic and PIC-specific entry
-	with reg args. */
 
 static void
 generateEnilopmarts(void)
@@ -7701,27 +7333,6 @@
 	cePrimReturnEnterCogCodeProfiling = methodZoneBase;
 	outputInstructionsForGeneratedRuntimeAt(cePrimReturnEnterCogCodeProfiling);
 	recordGeneratedRunTimeaddress("cePrimReturnEnterCogCodeProfiling", cePrimReturnEnterCogCodeProfiling);
-	
-#  if Debug
-	realCEEnterCogCodePopReceiverArg0Regs = genEnilopmartForandcalled(ReceiverResultReg, Arg0Reg, "realCEEnterCogCodePopReceiverArg0Regs");
-	ceEnterCogCodePopReceiverArg0Regs = enterCogCodePopReceiverArg0Regs;
-	realCEEnterCogCodePopReceiverArg1Arg0Regs = genEnilopmartForandandcalled(ReceiverResultReg, Arg0Reg, Arg1Reg, "realCEEnterCogCodePopReceiverArg1Arg0Regs");
-	ceEnterCogCodePopReceiverArg1Arg0Regs = enterCogCodePopReceiverArg1Arg0Regs;
-
-#  else /* Debug */
-	ceEnterCogCodePopReceiverArg0Regs = genEnilopmartForandcalled(ReceiverResultReg, Arg0Reg, "ceEnterCogCodePopReceiverArg0Regs");
-	ceEnterCogCodePopReceiverArg1Arg0Regs = genEnilopmartForandandcalled(ReceiverResultReg, Arg0Reg, Arg1Reg, "ceEnterCogCodePopReceiverArg1Arg0Regs");
-
-#  endif /* Debug */
-
-	ceEnter0ArgsPIC = genEnterPICEnilopmartNumArgs(0);
-	if ((numRegArgs()) >= 1) {
-		ceEnter1ArgsPIC = genEnterPICEnilopmartNumArgs(1);
-		if ((numRegArgs()) >= 2) {
-			ceEnter1ArgsPIC = genEnterPICEnilopmartNumArgs(2);
-			assert((numRegArgs()) == 2);
-		}
-	}
 }
 
 
@@ -7876,17 +7487,9 @@
 static void
 generateMissAbortTrampolines(void)
 {
-    sqInt numArgs;
-
-	for (numArgs = 0; numArgs <= ((numRegArgs()) + 1); numArgs += 1) {
-		methodAbortTrampolines[numArgs] = (genMethodAbortTrampolineFor(numArgs));
-	}
-	for (numArgs = 0; numArgs <= ((numRegArgs()) + 1); numArgs += 1) {
-		picAbortTrampolines[numArgs] = (genPICAbortTrampolineFor(numArgs));
-	}
-	for (numArgs = 0; numArgs <= ((numRegArgs()) + 1); numArgs += 1) {
-		picMissTrampolines[numArgs] = (genPICMissTrampolineFor(numArgs));
-	}
+	ceMethodAbortTrampoline = genMethodAbortTrampoline();
+	cePICAbortTrampoline = genPICAbortTrampoline();
+	ceCPICMissTrampoline = genTrampolineForcalledargarg(ceCPICMissreceiver, "ceCPICMissTrampoline", ClassReg, ReceiverResultReg);
 	;
 }
 
@@ -7946,9 +7549,6 @@
 }
 
 
-/*	Override to generate code to push the register arg(s) for <= numRegArg
-	arity sends.
- */
 /*	Slang needs these apparently superfluous asSymbol sends. */
 
 static void
@@ -7957,13 +7557,13 @@
     sqInt numArgs;
 
 	for (numArgs = 0; numArgs <= (NumSendTrampolines - 2); numArgs += 1) {
-		sendTrampolines[numArgs] = (genSendTrampolineFornumArgscalledargargargarg(ceSendsupertonumArgs, numArgs, trampolineNamenumArgs("ceSend", numArgs), ClassReg, 0, ReceiverResultReg, numArgs));
+		sendTrampolines[numArgs] = (genTrampolineForcalledargargargarg(ceSendsupertonumArgs, trampolineNamenumArgs("ceSend", numArgs), ClassReg, 0, ReceiverResultReg, numArgs));
 	}
-	sendTrampolines[NumSendTrampolines - 1] = (genSendTrampolineFornumArgscalledargargargarg(ceSendsupertonumArgs, (numRegArgs()) + 1, trampolineNamenumArgs("ceSend", -1), ClassReg, 0, ReceiverResultReg, SendNumArgsReg));
+	sendTrampolines[NumSendTrampolines - 1] = (genTrampolineForcalledargargargarg(ceSendsupertonumArgs, trampolineNamenumArgs("ceSend", -1), ClassReg, 0, ReceiverResultReg, SendNumArgsReg));
 	for (numArgs = 0; numArgs <= (NumSendTrampolines - 2); numArgs += 1) {
-		superSendTrampolines[numArgs] = (genSendTrampolineFornumArgscalledargargargarg(ceSendsupertonumArgs, numArgs, trampolineNamenumArgs("ceSuperSend", numArgs), ClassReg, 1, ReceiverResultReg, numArgs));
+		superSendTrampolines[numArgs] = (genTrampolineForcalledargargargarg(ceSendsupertonumArgs, trampolineNamenumArgs("ceSuperSend", numArgs), ClassReg, 1, ReceiverResultReg, numArgs));
 	}
-	superSendTrampolines[NumSendTrampolines - 1] = (genSendTrampolineFornumArgscalledargargargarg(ceSendsupertonumArgs, (numRegArgs()) + 1, trampolineNamenumArgs("ceSuperSend", -1), ClassReg, 1, ReceiverResultReg, SendNumArgsReg));
+	superSendTrampolines[NumSendTrampolines - 1] = (genTrampolineForcalledargargargarg(ceSendsupertonumArgs, trampolineNamenumArgs("ceSuperSend", -1), ClassReg, 1, ReceiverResultReg, SendNumArgsReg));
 	firstSend = sendTrampolines[0];
 	lastSend = superSendTrampolines[NumSendTrampolines - 1];
 }
@@ -8003,7 +7603,7 @@
 {
 	ceTraceLinkedSendTrampoline = genSafeTrampolineForcalledarg(ceTraceLinkedSend, "ceTraceLinkedSendTrampoline", ReceiverResultReg);
 	ceTraceBlockActivationTrampoline = genTrampolineForcalled(ceTraceBlockActivation, "ceTraceBlockActivationTrampoline");
-	ceTraceStoreTrampoline = genSafeTrampolineForcalledargarg(ceTraceStoreOfinto, "ceTraceStoreTrampoline", TempReg, ReceiverResultReg);
+	ceTraceStoreTrampoline = genSafeTrampolineForcalledargarg(ceTraceStoreOfinto, "ceTraceStoreTrampoline", ClassReg, ReceiverResultReg);
 }
 
 
@@ -8473,7 +8073,6 @@
 static sqInt
 genJumpBackTo(sqInt targetBytecodePC)
 {
-	ssFlushTo(simStackPtr);
 	gMoveAwR(stackLimitAddress(), TempReg);
 	gCmpRR(TempReg, SPReg);
 	gJumpAboveOrEqual(fixupAt(targetBytecodePC - initialPC));
@@ -8530,25 +8129,19 @@
 	return jumpToTarget;
 }
 
+
+/*	Cunning trick by LPD. If true and false are contiguous subtract the
+	smaller. Correct result is either 0 or the distance between them. If
+	result is not 0 or
+	their distance send mustBeBoolean. */
+
 static sqInt
 genJumpIfto(sqInt boolean, sqInt targetBytecodePC)
 {
-    CogSimStackEntry *desc;
     AbstractInstruction *ok;
 
-	ssFlushTo(simStackPtr - 1);
-	desc = ssTop();
-	ssPop(1);
-	if ((((desc->type)) == SSConstant)
-	 && ((((desc->constant)) == (trueObject()))
- || (((desc->constant)) == (falseObject())))) {
-		annotateBytecode((((desc->constant)) == boolean
-			? gJump(ensureFixupAt(targetBytecodePC - initialPC))
-			: gLabel()));
-		return 0;
-	}
-	popToReg(desc, TempReg);
 	assert((objectAfter(falseObject())) == (trueObject()));
+	gPopR(TempReg);
 	annotateobjRef(gSubCwR(boolean, TempReg), boolean);
 	gJumpZero(ensureFixupAt(targetBytecodePC - initialPC));
 	gCmpCqR((boolean == (falseObject())
@@ -8579,7 +8172,6 @@
 static sqInt
 genJumpTo(sqInt targetBytecodePC)
 {
-	ssFlushTo(simStackPtr);
 	gJump(ensureFixupAt(targetBytecodePC - initialPC));
 	return 0;
 }
@@ -8676,39 +8268,7 @@
 	return genJumpTo(targetpc);
 }
 
-static sqInt
-genMarshalledSendSupernumArgs(sqInt selector, sqInt numArgs)
-{
-	if (isYoung(selector)) {
-		hasYoungReferent = 1;
-	}
-	assert(needsFrame);
-	if (numArgs > 2) {
-		gMoveCqR(numArgs, SendNumArgsReg);
-	}
-	gMoveCwR(selector, ClassReg);
-	CallSend(superSendTrampolines[((numArgs < (NumSendTrampolines - 1)) ? numArgs : (NumSendTrampolines - 1))]);
-	(optStatus.isReceiverResultRegLive = 0);
-	return ssPushRegister(ReceiverResultReg);
-}
 
-static sqInt
-genMarshalledSendnumArgs(sqInt selector, sqInt numArgs)
-{
-	if (isYoung(selector)) {
-		hasYoungReferent = 1;
-	}
-	assert(needsFrame);
-	if (numArgs > 2) {
-		gMoveCqR(numArgs, SendNumArgsReg);
-	}
-	gMoveCwR(selector, ClassReg);
-	CallSend(sendTrampolines[((numArgs < (NumSendTrampolines - 1)) ? numArgs : (NumSendTrampolines - 1))]);
-	(optStatus.isReceiverResultRegLive = 0);
-	return ssPushRegister(ReceiverResultReg);
-}
-
-
 /*	Generate the abort for a method. This abort performs either a call of
 	ceSICMiss: to handle a single-in-line cache miss or a call of
 	ceStackOverflow: to handle a
@@ -8720,7 +8280,7 @@
 	miss.  */
 
 static sqInt
-genMethodAbortTrampolineFor(sqInt numArgs)
+genMethodAbortTrampoline(void)
 {
     AbstractInstruction *jumpSICMiss;
 
@@ -8729,10 +8289,7 @@
 	jumpSICMiss = gJumpNonZero(0);
 	compileTrampolineForcallJumpBarnumArgsargargargargsaveRegsresultReg(ceStackOverflow, 1, 1, SendNumArgsReg, null, null, null, 0, null);
 	jmpTarget(jumpSICMiss, gLabel());
-	genPushRegisterArgsForAbortMissNumArgs(numArgs);
-	return genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(ceSICMiss, trampolineNamenumArgs("ceMethodAbort", (numArgs <= (numRegArgs())
-		? numArgs
-		: -1)), 1, 1, ReceiverResultReg, null, null, null, 0, null, 1);
+	return genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(ceSICMiss, "ceMethodAbort", 1, 1, ReceiverResultReg, null, null, null, 0, null, 1);
 }
 
 static void
@@ -8785,71 +8342,62 @@
 	ClassReg. If the register is zero then this is an MNU. */
 
 static sqInt
-genPICAbortTrampolineFor(sqInt numArgs)
+genPICAbortTrampoline(void)
 {
 	opcodeIndex = 0;
-	genPushRegisterArgsForAbortMissNumArgs(numArgs);
-	return genInnerPICAbortTrampoline(trampolineNamenumArgs("cePICAbort", (numArgs <= (numRegArgs())
-		? numArgs
-		: -1)));
+	return genInnerPICAbortTrampoline("cePICAbort");
 }
 
 static sqInt
-genPICMissTrampolineFor(sqInt numArgs)
-{
-    sqInt startAddress;
-
-	startAddress = methodZoneBase;
-
-	/* N.B. a closed PIC jumps to the miss routine, not calls it, so there is only one retpc on the stack. */
-
-	opcodeIndex = 0;
-	genPushRegisterArgsForNumArgs(numArgs);
-	genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(ceCPICMissreceiver, trampolineNamenumArgs("cePICMiss", (numArgs <= (numRegArgs())
-		? numArgs
-		: -1)), 1, 2, ClassReg, ReceiverResultReg, null, null, 0, null, 1);
-	return startAddress;
-}
-
-static sqInt
 genPopStackBytecode(void)
 {
-	if ((ssTop()->spilled)) {
-		gAddCqR(BytesPerWord, SPReg);
-	}
-	ssPop(1);
+	gAddCqR(BytesPerWord, SPReg);
 	return 0;
 }
 
+
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
+	return address */
+
 static sqInt
 genPrimitiveAdd(void)
 {
     AbstractInstruction *jumpNotSI;
     AbstractInstruction *jumpOvfl;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
 	genRemoveSmallIntegerTagsInScratchReg(ClassReg);
-	gAddRR(ReceiverResultReg, ClassReg);
+	gMoveRR(ReceiverResultReg, TempReg);
+	gAddRR(ClassReg, TempReg);
 	jumpOvfl = gJumpOverflow(0);
-	gMoveRR(ClassReg, ReceiverResultReg);
-	gRetN(0);
+	gMoveRR(TempReg, ReceiverResultReg);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpOvfl, jmpTarget(jumpNotSI, gLabel()));
 	return 0;
 }
 
+
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	return address */
+
 static sqInt
 genPrimitiveAsFloat(void)
 {
     AbstractInstruction *jumpFailAlloc;
 
-	gMoveRR(ReceiverResultReg, TempReg);
-	genConvertSmallIntegerToIntegerInScratchReg(TempReg);
-	gConvertRRd(TempReg, DPFPReg0);
+	gMoveRR(ReceiverResultReg, ClassReg);
+	genConvertSmallIntegerToIntegerInScratchReg(ClassReg);
+	gConvertRRd(ClassReg, DPFPReg0);
 	jumpFailAlloc = genAllocFloatValueintoscratchRegscratchReg(DPFPReg0, SendNumArgsReg, ClassReg, TempReg);
 	gMoveRR(SendNumArgsReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord);
 	jmpTarget(jumpFailAlloc, gLabel());
 	compileInterpreterPrimitive(functionPointerForCompiledMethodprimitiveIndex(methodObj, primitiveIndex));
 	return 0;
@@ -8858,8 +8406,8 @@
 static sqInt
 genPrimitiveAt(void)
 {
-	assert((numRegArgs()) >= 1);
-	return genInnerPrimitiveAt(0);
+	gMoveMwrR(BytesPerWord, SPReg, Arg0Reg);
+	return genInnerPrimitiveAt(BytesPerWord * 2);
 }
 
 static sqInt
@@ -8867,13 +8415,15 @@
 {
     AbstractInstruction *jumpNotSI;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 
-	/* Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them. */
+	/* Whether the SmallInteger tags are zero or non-zero, anding them together will preserve them. */
 
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
-	gAndRR(Arg0Reg, ReceiverResultReg);
-	gRetN(0);
+	gAndRR(ClassReg, ReceiverResultReg);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpNotSI, gLabel());
 	return 0;
 }
@@ -8883,23 +8433,26 @@
 {
     AbstractInstruction *jumpNotSI;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 
 	/* Whether the SmallInteger tags are zero or non-zero, oring them together will preserve them. */
 
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
-	gOrRR(Arg0Reg, ReceiverResultReg);
-	gRetN(0);
+	gOrRR(ClassReg, ReceiverResultReg);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpNotSI, gLabel());
 	return 0;
 }
 
 
-/*	Receiver and arg in registers.
-	Stack looks like
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
 	return address
 	
-	rTemp := rArg0
+	rTemp := ArgOffset(SP)
 	rClass := tTemp
 	rTemp := rTemp & 1
 	jz nonInt
@@ -8941,9 +8494,8 @@
     AbstractInstruction *jumpOvfl;
     AbstractInstruction *jumpTooBig;
 
-	assert((numRegArgs()) >= 1);
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
 	genConvertSmallIntegerToIntegerInScratchReg(ClassReg);
 	if (!(setsConditionCodesFor(lastOpcode(), JumpNegative))) {
@@ -8960,14 +8512,14 @@
 	genRemoveSmallIntegerTagsInScratchReg(ReceiverResultReg);
 	gLogicalShiftLeftRR(ClassReg, ReceiverResultReg);
 	genAddSmallIntegerTagsTo(ReceiverResultReg);
-	gRetN(0);
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpNegative, gNegateR(ClassReg));
 	gCmpCqR(numSmallIntegerBits(), ClassReg);
 	jumpInRange = gJumpLessOrEqual(0);
 	gMoveCqR(numSmallIntegerBits(), ClassReg);
 	jmpTarget(jumpInRange, gArithmeticShiftRightRR(ClassReg, ReceiverResultReg));
 	genSetSmallIntegerTagsIn(ReceiverResultReg);
-	gRetN(0);
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpNotSI, jmpTarget(jumpTooBig, jmpTarget(jumpOvfl, gLabel())));
 	return 0;
 }
@@ -8977,14 +8529,16 @@
 {
     AbstractInstruction *jumpNotSI;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 
 	/* Clear one or the other tag so that xoring will preserve them. */
 
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
-	genRemoveSmallIntegerTagsInScratchReg(Arg0Reg);
-	gXorRR(Arg0Reg, ReceiverResultReg);
-	gRetN(0);
+	genRemoveSmallIntegerTagsInScratchReg(ClassReg);
+	gXorRR(ClassReg, ReceiverResultReg);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpNotSI, gLabel());
 	return 0;
 }
@@ -8996,13 +8550,6 @@
 	block entry or the no-context-switch entry, as appropriate, and we're
 	done. If not,
 	invoke the interpreter primitive. */
-/*	Check the argument count. Fail if wrong.
-	Get the method from the outerContext and see if it is cogged. If so, jump
-	to the
-	block entry or the no-context-switch entry, as appropriate, and we're
-	done. If not,
-	invoke the interpreter primitive.
-	Override to push the register args first. */
 
 static sqInt
 genPrimitiveClosureValue(void)
@@ -9012,7 +8559,6 @@
     void (*primitiveRoutine)();
     sqInt result;
 
-	genPushRegisterArgs();
 	genLoadSlotsourceRegdestReg(ClosureNumArgsIndex, ReceiverResultReg, TempReg);
 	gCmpCqR(((methodOrBlockNumArgs << 1) | 1), TempReg);
 	jumpFail = gJumpNonZero(0);
@@ -9045,9 +8591,9 @@
     AbstractInstruction *jumpSameSign;
     AbstractInstruction *jumpZero;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
-	gMoveRR(Arg0Reg, Arg1Reg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
+	gMoveRR(TempReg, Arg1Reg);
 
 	/* We must shift away the tags, not just subtract them, so that the
 	 overflow case doesn't actually overflow the machine instruction. */
@@ -9075,7 +8621,8 @@
 	jmpTarget(jumpSameSign, convert = gLabel());
 	genConvertIntegerToSmallIntegerInScratchReg(TempReg);
 	gMoveRR(TempReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpExact, gCmpCqR(1 << ((numSmallIntegerBits()) - 1), TempReg));
 	gJumpLess(convert);
 	jmpTarget(jumpZero, jmpTarget(jumpNotSI, gLabel()));
@@ -9090,8 +8637,8 @@
     AbstractInstruction *jumpOverflow;
     AbstractInstruction *jumpZero;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 
 	/* We must shift away the tags, not just subtract them, so that the
 	 overflow case doesn't actually overflow the machine instruction. */
@@ -9111,7 +8658,8 @@
 	jumpOverflow = gJumpGreaterOrEqual(0);
 	genConvertIntegerToSmallIntegerInScratchReg(TempReg);
 	gMoveRR(TempReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpOverflow, jmpTarget(jumpInexact, jmpTarget(jumpZero, jmpTarget(jumpNotSI, gLabel()))));
 	return 0;
 }
@@ -9123,8 +8671,9 @@
 }
 
 
-/*	Receiver and arg in registers.
-	Stack looks like
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
 	return address */
 
 static sqInt
@@ -9132,12 +8681,14 @@
 {
     AbstractInstruction *jumpFalse;
 
-	gCmpRR(Arg0Reg, ReceiverResultReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gCmpRR(TempReg, ReceiverResultReg);
 	jumpFalse = gJumpNonZero(0);
 	annotateobjRef(gMoveCwR(trueObject(), ReceiverResultReg), trueObject());
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpFalse, annotateobjRef(gMoveCwR(falseObject(), ReceiverResultReg), falseObject()));
-	gRetN(0);
+	gRetN(BytesPerWord * 2);
 	return 0;
 }
 
@@ -9195,6 +8746,11 @@
 	return genDoubleComparisoninvert(gJumpFPNotEqual, 0);
 }
 
+
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	return address */
+
 static sqInt
 genPrimitiveFloatSquareRoot(void)
 {
@@ -9204,7 +8760,8 @@
 	gSqrtRd(DPFPReg0);
 	jumpFailAlloc = genAllocFloatValueintoscratchRegscratchReg(DPFPReg0, SendNumArgsReg, ClassReg, TempReg);
 	gMoveRR(SendNumArgsReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord);
 	jmpTarget(jumpFailAlloc, gLabel());
 	compileInterpreterPrimitive(functionPointerForCompiledMethodprimitiveIndex(methodObj, primitiveIndex));
 	return 0;
@@ -9237,7 +8794,8 @@
 	jumpSI = genJumpSmallIntegerInScratchReg(ClassReg);
 	genGetHashFieldNonIntOfasSmallIntegerInto(ReceiverResultReg, TempReg);
 	gMoveRR(TempReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord);
 	jmpTarget(jumpSI, gLabel());
 	return 0;
 }
@@ -9262,8 +8820,8 @@
     AbstractInstruction *jumpSameSign;
     AbstractInstruction *jumpZero;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
 	genRemoveSmallIntegerTagsInScratchReg(ClassReg);
 	jumpZero = gJumpZero(0);
@@ -9286,7 +8844,8 @@
 	jmpTarget(jumpSameSign, jmpTarget(jumpExact, gLabel()));
 	genSetSmallIntegerTagsIn(ClassReg);
 	gMoveRR(ClassReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpZero, jmpTarget(jumpNotSI, gLabel()));
 	return 0;
 }
@@ -9297,17 +8856,18 @@
     AbstractInstruction *jumpNotSI;
     AbstractInstruction *jumpOvfl;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
-	gMoveRR(ReceiverResultReg, Arg1Reg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
 	genShiftAwaySmallIntegerTagsInScratchReg(ClassReg);
-	genRemoveSmallIntegerTagsInScratchReg(Arg1Reg);
-	gMulRR(Arg1Reg, ClassReg);
+	gMoveRR(ReceiverResultReg, TempReg);
+	genRemoveSmallIntegerTagsInScratchReg(TempReg);
+	gMulRR(TempReg, ClassReg);
 	jumpOvfl = gJumpOverflow(0);
 	genSetSmallIntegerTagsIn(ClassReg);
 	gMoveRR(ClassReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpOvfl, jmpTarget(jumpNotSI, gLabel()));
 	return 0;
 }
@@ -9325,8 +8885,8 @@
     AbstractInstruction *jumpOverflow;
     AbstractInstruction *jumpZero;
 
-	gMoveRR(Arg0Reg, TempReg);
-	gMoveRR(Arg0Reg, ClassReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 
 	/* We must shift away the tags, not just subtract them, so that the
 	 overflow case doesn't actually overflow the machine instruction. */
@@ -9344,7 +8904,8 @@
 	jumpOverflow = gJumpGreaterOrEqual(0);
 	genConvertIntegerToSmallIntegerInScratchReg(TempReg);
 	gMoveRR(TempReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpOverflow, jmpTarget(jumpZero, jmpTarget(jumpNotSI, gLabel())));
 	return 0;
 }
@@ -9352,30 +8913,38 @@
 static sqInt
 genPrimitiveSize(void)
 {
-	return genInnerPrimitiveSize(0);
+	return genInnerPrimitiveSize(BytesPerWord);
 }
 
 static sqInt
 genPrimitiveStringAt(void)
 {
-	assert((numRegArgs()) >= 1);
-	return genInnerPrimitiveStringAt(0);
+	gMoveMwrR(BytesPerWord, SPReg, Arg0Reg);
+	return genInnerPrimitiveStringAt(BytesPerWord * 2);
 }
 
+
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
+	return address */
+
 static sqInt
 genPrimitiveSubtract(void)
 {
     AbstractInstruction *jumpNotSI;
     AbstractInstruction *jumpOvfl;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpNotSI = genJumpNotSmallIntegerInScratchReg(TempReg);
 	gMoveRR(ReceiverResultReg, TempReg);
-	gSubRR(Arg0Reg, TempReg);
+	gSubRR(ClassReg, TempReg);
 	jumpOvfl = gJumpOverflow(0);
 	genAddSmallIntegerTagsTo(TempReg);
 	gMoveRR(TempReg, ReceiverResultReg);
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpOvfl, jmpTarget(jumpNotSI, gLabel()));
 	return 0;
 }
@@ -9449,10 +9018,9 @@
 genPushActiveContextBytecode(void)
 {
 	assert(needsFrame);
-	(optStatus.isReceiverResultRegLive = 0);
-	ssAllocateCallReg(ReceiverResultReg);
 	CallRT(cePushActiveContextTrampoline);
-	return ssPushRegister(ReceiverResultReg);
+	gPushR(ReceiverResultReg);
+	return 0;
 }
 
 
@@ -9486,18 +9054,18 @@
 
 	assert(needsFrame);
 	addBlockStartAtnumArgsnumCopiedspan(bytecodePointer + 4, byte1 & 15, numCopied = ((usqInt) byte1) >> 4, (byte2 << 8) + byte3);
-	if (numCopied > 0) {
-		ssFlushTo(simStackPtr);
-	}
-	(optStatus.isReceiverResultRegLive = 0);
-	ssAllocateCallRegand(SendNumArgsReg, ReceiverResultReg);
 	gMoveCqR(byte1 | ((bytecodePointer + 5) << 8), SendNumArgsReg);
 	CallRT(ceClosureCopyTrampoline);
 	if (numCopied > 0) {
-		gAddCqR(numCopied * BytesPerWord, SPReg);
-		ssPop(numCopied);
+		if (numCopied > 1) {
+			gAddCqR((numCopied - 1) * BytesPerWord, SPReg);
+		}
+		gMoveRMwr(ReceiverResultReg, 0, SPReg);
 	}
-	return ssPushRegister(ReceiverResultReg);
+	else {
+		gPushR(ReceiverResultReg);
+	}
+	return 0;
 }
 
 static sqInt
@@ -9546,25 +9114,22 @@
 genPushLiteralVariable(sqInt literalIndex)
 {
     sqInt association;
-    sqInt freeReg;
 
-	freeReg = ssAllocatePreferredReg(ClassReg);
 
 	/* N.B. Do _not_ use ReceiverResultReg to avoid overwriting receiver in assignment in frameless methods. */
-	/* So far descriptors are not rich enough to describe the entire dereference so generate the register
-	 load but don't push the result.  There is an order-or-evaluation issue if we defer the dereference. */
 
 	association = literalofMethod(literalIndex, methodObj);
-	annotateobjRef(gMoveCwR(association, TempReg), association);
-	genLoadSlotsourceRegdestReg(ValueIndex, TempReg, freeReg);
-	ssPushRegister(freeReg);
+	annotateobjRef(gMoveCwR(association, ClassReg), association);
+	genLoadSlotsourceRegdestReg(ValueIndex, ClassReg, TempReg);
+	gPushR(TempReg);
 	return 0;
 }
 
 static sqInt
 genPushLiteral(sqInt literal)
 {
-	return ssPushConstant(literal);
+	annotateobjRef(gPushCw(literal), literal);
+	return 0;
 }
 
 static sqInt
@@ -9574,16 +9139,14 @@
     AbstractInstruction *jmpSingle;
 
 	assert(needsFrame);
-	ssAllocateCallRegand(ReceiverResultReg, SendNumArgsReg);
-	ensureReceiverResultRegContainsSelf();
-	if ((registerMaskFor(ReceiverResultReg)) & callerSavedRegMask) {
-		(optStatus.isReceiverResultRegLive = 0);
-	}
 	if (slotIndex == InstructionPointerIndex) {
+		gMoveMwrR(FoxMFReceiver, FPReg, ReceiverResultReg);
 		gMoveCqR(slotIndex, SendNumArgsReg);
 		CallRT(ceFetchContextInstVarTrampoline);
-		return ssPushRegister(SendNumArgsReg);
+		gPushR(SendNumArgsReg);
+		return 0;
 	}
+	gMoveMwrR(FoxMFReceiver, FPReg, ReceiverResultReg);
 	genLoadSlotsourceRegdestReg(SenderIndex, ReceiverResultReg, TempReg);
 	jmpSingle = genJumpNotSmallIntegerInScratchReg(TempReg);
 	gMoveCqR(slotIndex, SendNumArgsReg);
@@ -9591,8 +9154,8 @@
 	jmpDone = gJump(0);
 	jmpTarget(jmpSingle, gLabel());
 	genLoadSlotsourceRegdestReg(slotIndex, ReceiverResultReg, SendNumArgsReg);
-	jmpTarget(jmpDone, gLabel());
-	return ssPushRegister(SendNumArgsReg);
+	jmpTarget(jmpDone, gPushR(SendNumArgsReg));
+	return 0;
 }
 
 static sqInt
@@ -9603,13 +9166,7 @@
     sqInt size;
 
 	assert(needsFrame);
-	(optStatus.isReceiverResultRegLive = 0);
-	if ((popValues = byte1 > 127)) {
-		ssFlushTo(simStackPtr);
-	}
-	else {
-		ssAllocateCallRegand(SendNumArgsReg, ReceiverResultReg);
-	}
+	popValues = byte1 > 127;
 	size = byte1 & 127;
 	gMoveCqR(size, SendNumArgsReg);
 	CallRT(ceCreateNewArrayTrampoline);
@@ -9618,9 +9175,9 @@
 			gPopR(TempReg);
 			genStoreSourceRegslotIndexintoNewObjectInDestReg(TempReg, i, ReceiverResultReg);
 		}
-		ssPop(size);
 	}
-	return ssPushRegister(ReceiverResultReg);
+	gPushR(ReceiverResultReg);
+	return 0;
 }
 
 static sqInt
@@ -9632,7 +9189,14 @@
 static sqInt
 genPushReceiverBytecode(void)
 {
-	return ssPushDesc(simSelf);
+	if (needsFrame) {
+		gMoveMwrR(FoxMFReceiver, FPReg, TempReg);
+		gPushR(TempReg);
+	}
+	else {
+		gPushR(ReceiverResultReg);
+	}
+	return 0;
 }
 
 static sqInt
@@ -9644,113 +9208,26 @@
 static sqInt
 genPushReceiverVariable(sqInt index)
 {
-	ensureReceiverResultRegContainsSelf();
-	return genSSPushSlotreg(index, ReceiverResultReg);
-}
+    sqInt maybeErr;
 
-
-/*	Ensure that the register args are pushed before the retpc for methods with
-	arity <= self numRegArgs.
- */
-/*	This won't be as clumsy on a RISC. But putting the receiver and
-	args above the return address means the CoInterpreter has a
-	single machine-code frame format which saves us a lot of work. */
-
-static void
-genPushRegisterArgs(void)
-{
-	if (!(regArgsHaveBeenPushed
-		 || (methodOrBlockNumArgs > (numRegArgs())))) {
-		genPushRegisterArgsForNumArgs(methodOrBlockNumArgs);
-		regArgsHaveBeenPushed = 1;
+	if (needsFrame) {
+		gMoveMwrR(FoxMFReceiver, FPReg, ReceiverResultReg);
 	}
-}
-
-
-/*	Ensure that the register args are pushed before the outer and
-	inner retpcs at an entry miss for arity <= self numRegArgs. The
-	outer retpc is that of a call at a send site. The inner is the call
-	from a method or PIC abort/miss to the trampoline. */
-/*	This won't be as clumsy on a RISC. But putting the receiver and
-	args above the return address means the CoInterpreter has a
-	single machine-code frame format which saves us a lot of work. */
-/*	Iff there are register args convert
-	base	->	outerRetpc		(send site retpc)
-	sp		->	innerRetpc		(PIC abort/miss retpc)
-	to
-	base	->	receiver
-	(arg0)
-	(arg1)
-	outerRetpc
-	sp		->	innerRetpc		(PIC abort/miss retpc) */
-
-static void
-genPushRegisterArgsForAbortMissNumArgs(sqInt numArgs)
-{
-	if (numArgs <= (numRegArgs())) {
-		assert((numRegArgs()) <= 2);
-		if (numArgs == 0) {
-			gMoveMwrR(0, SPReg, TempReg);
-			gPushR(TempReg);
-			gMoveMwrR(BytesPerWord * 2, SPReg, TempReg);
-			gMoveRMwr(TempReg, BytesPerWord, SPReg);
-			gMoveRMwr(ReceiverResultReg, 2 * BytesPerWord, SPReg);
-			return;
-		}
-		if (numArgs == 1) {
-			gMoveMwrR(BytesPerWord, SPReg, TempReg);
-			gPushR(TempReg);
-			gMoveMwrR(BytesPerWord, SPReg, TempReg);
-			gPushR(TempReg);
-			gMoveRMwr(ReceiverResultReg, 3 * BytesPerWord, SPReg);
-			gMoveRMwr(Arg0Reg, 2 * BytesPerWord, SPReg);
-			return;
-		}
-		if (numArgs == 2) {
-			gPushR(Arg1Reg);
-			gMoveMwrR(BytesPerWord * 2, SPReg, TempReg);
-			gPushR(TempReg);
-			gMoveMwrR(BytesPerWord * 2, SPReg, TempReg);
-			gPushR(TempReg);
-			gMoveRMwr(ReceiverResultReg, 4 * BytesPerWord, SPReg);
-			gMoveRMwr(Arg0Reg, 3 * BytesPerWord, SPReg);
-			return;
-		}
+	maybeErr = genLoadSlotsourceRegdestReg(index, ReceiverResultReg, TempReg);
+	if (maybeErr < 0) {
+		return maybeErr;
 	}
+	gPushR(TempReg);
+	return 0;
 }
 
-
-/*	Ensure that the register args are pushed before the retpc for arity <=
-	self numRegArgs.
- */
-/*	This won't be as clumsy on a RISC. But putting the receiver and
-	args above the return address means the CoInterpreter has a
-	single machine-code frame format which saves us a lot of work. */
-
-static void
-genPushRegisterArgsForNumArgs(sqInt numArgs)
-{
-	if (numArgs <= (numRegArgs())) {
-		gMoveMwrR(0, SPReg, TempReg);
-		gMoveRMwr(ReceiverResultReg, 0, SPReg);
-		assert((numRegArgs()) <= 2);
-		if (numArgs > 0) {
-			gPushR(Arg0Reg);
-			if (numArgs > 1) {
-				gPushR(Arg1Reg);
-			}
-		}
-		gPushR(TempReg);
-	}
-}
-
 static sqInt
 genPushRemoteTempLongBytecode(void)
 {
-	ssAllocateRequiredRegand(ClassReg, SendNumArgsReg);
 	gMoveMwrR(frameOffsetOfTemporary(byte2), FPReg, ClassReg);
-	genLoadSlotsourceRegdestReg(byte1, ClassReg, SendNumArgsReg);
-	return ssPushRegister(SendNumArgsReg);
+	genLoadSlotsourceRegdestReg(byte1, ClassReg, TempReg);
+	gPushR(TempReg);
+	return 0;
 }
 
 static sqInt
@@ -9762,7 +9239,9 @@
 static sqInt
 genPushTemporaryVariable(sqInt index)
 {
-	return ssPushDesc(simStack[index]);
+	gMoveMwrR(frameOffsetOfTemporary(index), FPReg, TempReg);
+	gPushR(TempReg);
+	return 0;
 }
 
 
@@ -9909,8 +9388,8 @@
 genReturnTopFromBlock(void)
 {
 	assert(inBlock);
-	popToReg(ssTop(), ReceiverResultReg);
-	ssPop(1);
+	flag("currently caller pushes result");
+	gPopR(ReceiverResultReg);
 	if (needsFrame) {
 		gMoveRR(FPReg, SPReg);
 		gPopR(FPReg);
@@ -9919,11 +9398,16 @@
 	return 0;
 }
 
+
+/*	Return pops receiver and arguments off the stack. Callee pushes the
+	result. 
+ */
+
 static sqInt
 genReturnTopFromMethod(void)
 {
-	popToReg(ssTop(), ReceiverResultReg);
-	ssPop(1);
+	flag("currently caller pushes result");
+	gPopR(ReceiverResultReg);
 	return genUpArrowReturn();
 }
 
@@ -10006,32 +9490,37 @@
 static sqInt
 genSendSupernumArgs(sqInt selector, sqInt numArgs)
 {
-	marshallSendArguments(numArgs);
-	return genMarshalledSendSupernumArgs(selector, numArgs);
+	assert(needsFrame);
+	if (isYoung(selector)) {
+		hasYoungReferent = 1;
+	}
+	gMoveMwrR(numArgs * BytesPerWord, SPReg, ReceiverResultReg);
+	if (numArgs > 2) {
+		gMoveCqR(numArgs, SendNumArgsReg);
+	}
+	gMoveCwR(selector, ClassReg);
+	CallSend(superSendTrampolines[((numArgs < (NumSendTrampolines - 1)) ? numArgs : (NumSendTrampolines - 1))]);
+	flag("currently caller pushes result");
+	gPushR(ReceiverResultReg);
+	return 0;
 }
 
-
-/*	Generate a trampoline with four arguments.
-	Hack: a negative value indicates an abstract register, a non-negative
-	value indicates a constant. */
-
 static sqInt
-genSendTrampolineFornumArgscalledargargargarg(void *aRoutine, sqInt numArgs, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt regOrConst2, sqInt regOrConst3)
-{
-    sqInt startAddress;
-
-	startAddress = methodZoneBase;
-	opcodeIndex = 0;
-	genPushRegisterArgsForNumArgs(numArgs);
-	genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(aRoutine, aString, 1, 4, regOrConst0, regOrConst1, regOrConst2, regOrConst3, 0, null, 1);
-	return startAddress;
-}
-
-static sqInt
 genSendnumArgs(sqInt selector, sqInt numArgs)
 {
-	marshallSendArguments(numArgs);
-	return genMarshalledSendnumArgs(selector, numArgs);
+	if (isYoung(selector)) {
+		hasYoungReferent = 1;
+	}
+	assert(needsFrame);
+	gMoveMwrR(numArgs * BytesPerWord, SPReg, ReceiverResultReg);
+	if (numArgs > 2) {
+		gMoveCqR(numArgs, SendNumArgsReg);
+	}
+	gMoveCwR(selector, ClassReg);
+	CallSend(sendTrampolines[((numArgs < (NumSendTrampolines - 1)) ? numArgs : (NumSendTrampolines - 1))]);
+	flag("currently caller pushes result");
+	gPushR(ReceiverResultReg);
+	return 0;
 }
 
 static sqInt
@@ -10063,367 +9552,55 @@
 	return genJumpTo(target);
 }
 
+
+/*	Stack looks like
+	receiver (also in ResultReceiverReg)
+	arg
+	return address */
+
 static sqInt
 genSmallIntegerComparison(sqInt jumpOpcode)
 {
     AbstractInstruction *jumpFail;
     AbstractInstruction *jumpTrue;
 
-	gMoveRR(Arg0Reg, TempReg);
+	gMoveMwrR(BytesPerWord, SPReg, TempReg);
+	gMoveRR(TempReg, ClassReg);
 	jumpFail = genJumpNotSmallIntegerInScratchReg(TempReg);
-	gCmpRR(Arg0Reg, ReceiverResultReg);
+	gCmpRR(ClassReg, ReceiverResultReg);
 	jumpTrue = gen(jumpOpcode);
 	annotateobjRef(gMoveCwR(falseObject(), ReceiverResultReg), falseObject());
-	gRetN(0);
+	flag("currently caller pushes result");
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpTrue, annotateobjRef(gMoveCwR(trueObject(), ReceiverResultReg), trueObject()));
-	gRetN(0);
+	gRetN(BytesPerWord * 2);
 	jmpTarget(jumpFail, gLabel());
 	return 0;
 }
 
 static sqInt
-genSpecialSelectorArithmetic(void)
-{
-    sqInt argInt;
-    sqInt argIsInt;
-    AbstractInstruction *jumpContinue;
-    AbstractInstruction *jumpNotSmallInts;
-    BytecodeDescriptor *primDescriptor;
-    sqInt rcvrInt;
-    sqInt rcvrIsInt;
-    sqInt result;
-
-	primDescriptor = generatorAt(byte0);
-	argIsInt = (((ssTop()->type)) == SSConstant)
-	 && ((((argInt = (ssTop()->constant))) & 1));
-	rcvrIsInt = (((ssValue(1)->type)) == SSConstant)
-	 && ((((rcvrInt = (ssValue(1)->constant))) & 1));
-	if (argIsInt
-	 && (rcvrIsInt)) {
-		rcvrInt = (rcvrInt >> 1);
-		argInt = (argInt >> 1);
-		
-		switch ((primDescriptor->opcode)) {
-		case AddRR:
-						result = rcvrInt + argInt;
-			break;
-		case SubRR:
-						result = rcvrInt - argInt;
-			break;
-		case AndRR:
-						result = rcvrInt && argInt;
-			break;
-		case OrRR:
-						result = rcvrInt || argInt;
-			break;
-		default:
-			error("Case not found and no otherwise clause");
-		}
-		if (isIntegerValue(result)) {
-			annotateBytecode(gLabel());
-			return ssPop(2),ssPushConstant(((result << 1) | 1));
-		}
-		return genSpecialSelectorSend();
-	}
-	if (!(argIsInt
-		 || (rcvrIsInt))) {
-		return genSpecialSelectorSend();
-	}
-	if (argIsInt) {
-		ssFlushTo(simStackPtr - 2);
-		popToReg(ssValue(1), ReceiverResultReg);
-		ssPop(2);
-		gMoveRR(ReceiverResultReg, TempReg);
-	}
-	else {
-		marshallSendArguments(1);
-		gMoveRR(Arg0Reg, TempReg);
-		if (!(rcvrIsInt)) {
-			if (isSmallIntegerTagNonZero()) {
-				gAndRR(ReceiverResultReg, TempReg);
-			}
-			else {
-				gOrRR(ReceiverResultReg, TempReg);
-			}
-		}
-	}
-	jumpNotSmallInts = genJumpNotSmallIntegerInScratchReg(TempReg);
-	
-	switch ((primDescriptor->opcode)) {
-	case AddRR:
-				if (argIsInt) {
-			gAddCqR(argInt - ConstZero, ReceiverResultReg);
-
-			/* overflow; must undo the damage before continuing */
-
-			jumpContinue = gJumpNoOverflow(0);
-			gSubCqR(argInt - ConstZero, ReceiverResultReg);
-		}
-		else {
-			genRemoveSmallIntegerTagsInScratchReg(ReceiverResultReg);
-			gAddRR(Arg0Reg, ReceiverResultReg);
-
-			/* overflow; must undo the damage before continuing */
-
-			jumpContinue = gJumpNoOverflow(0);
-			if (rcvrIsInt) {
-				gMoveCqR(rcvrInt, ReceiverResultReg);
-			}
-			else {
-				gSubRR(Arg0Reg, ReceiverResultReg);
-				genSetSmallIntegerTagsIn(ReceiverResultReg);
-			}
-		}
-		break;
-	case SubRR:
-				if (argIsInt) {
-			gSubCqR(argInt - ConstZero, ReceiverResultReg);
-
-			/* overflow; must undo the damage before continuing */
-
-			jumpContinue = gJumpNoOverflow(0);
-			gAddCqR(argInt - ConstZero, ReceiverResultReg);
-		}
-		else {
-			genRemoveSmallIntegerTagsInScratchReg(Arg0Reg);
-			gSubRR(Arg0Reg, ReceiverResultReg);
-
-			/* overflow; must undo the damage before continuing */
-
-			jumpContinue = gJumpNoOverflow(0);
-			gAddRR(Arg0Reg, ReceiverResultReg);
-			genSetSmallIntegerTagsIn(Arg0Reg);
-		}
-		break;
-	case AndRR:
-				if (argIsInt) {
-			gAndCqR(argInt, ReceiverResultReg);
-		}
-		else {
-			gAndRR(Arg0Reg, ReceiverResultReg);
-		}
-		jumpContinue = gJump(0);
-		break;
-	case OrRR:
-				if (argIsInt) {
-			gOrCqR(argInt, ReceiverResultReg);
-		}
-		else {
-			gOrRR(Arg0Reg, ReceiverResultReg);
-		}
-		jumpContinue = gJump(0);
-		break;
-	default:
-		error("Case not found and no otherwise clause");
-	}
-	jmpTarget(jumpNotSmallInts, gLabel());
-	if (argIsInt) {
-		gMoveCqR(argInt, Arg0Reg);
-	}
-	genMarshalledSendnumArgs(specialSelector(byte0 - 176), 1);
-	jmpTarget(jumpContinue, gLabel());
-	return 0;
-}
-
-static sqInt
 genSpecialSelectorClass(void)
 {
-	ssPop(1);
-	ssAllocateRequiredRegand(SendNumArgsReg, ClassReg);
-	ssPush(1);
-	popToReg(ssTop(), SendNumArgsReg);
+	gMoveMwrR(0, SPReg, SendNumArgsReg);
 	genGetClassObjectOfintoscratchReg(SendNumArgsReg, ClassReg, TempReg);
-	return ssPop(1),ssPushRegister(ClassReg);
+	gMoveRMwr(ClassReg, 0, SPReg);
+	return 0;
 }
 
 static sqInt
-genSpecialSelectorComparison(void)
-{
-    sqInt argInt;
-    sqInt argIsInt;
-    sqInt branchBytecode;
-    BytecodeDescriptor *branchDescriptor;
-    sqInt branchPC;
-    sqInt inlineCAB;
-    AbstractInstruction *jumpNotSmallInts;
-    sqInt postBranchPC;
-    BytecodeDescriptor *primDescriptor;
-    sqInt rcvrInt;
-    sqInt rcvrIsInt;
-    sqInt result;
-    sqInt targetBytecodePC;
-
-	ssFlushTo(simStackPtr - 2);
-	primDescriptor = generatorAt(byte0);
-	argIsInt = (((ssTop()->type)) == SSConstant)
-	 && ((((argInt = (ssTop()->constant))) & 1));
-	rcvrIsInt = (((ssValue(1)->type)) == SSConstant)
-	 && ((((rcvrInt = (ssValue(1)->constant))) & 1));
-	if (argIsInt
-	 && (rcvrIsInt)) {
-		;
-		
-		switch ((primDescriptor->opcode)) {
-		case JumpLess:
-						result = rcvrInt < argInt;
-			break;
-		case JumpLessOrEqual:
-						result = rcvrInt <= argInt;
-			break;
-		case JumpGreater:
-						result = rcvrInt > argInt;
-			break;
-		case JumpGreaterOrEqual:
-						result = rcvrInt >= argInt;
-			break;
-		case JumpZero:
-						result = rcvrInt == argInt;
-			break;
-		case JumpNonZero:
-						result = rcvrInt != argInt;
-			break;
-		default:
-			error("Case not found and no otherwise clause");
-		}
-		annotateBytecode(gLabel());
-		ssPop(2);
-		return ssPushConstant((result
-			? trueObject()
-			: falseObject()));
-	}
-	branchPC = bytecodePointer + ((primDescriptor->numBytes));
-	branchBytecode = fetchByteofObject(branchPC, methodObj);
-
-	/* Only interested in inlining if followed by a conditional branch. */
-
-	branchDescriptor = generatorAt(branchBytecode);
-
-	/* Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
-	 The relational operators successfully staticaly predict SmallIntegers; the equality operators do not. */
-
-	inlineCAB = ((branchDescriptor->isBranchTrue))
-	 || ((branchDescriptor->isBranchFalse));
-	if (inlineCAB
-	 && ((((primDescriptor->opcode)) == JumpZero)
- || (((primDescriptor->opcode)) == JumpNonZero))) {
-		inlineCAB = argIsInt
-		 || (rcvrIsInt);
-	}
-	if (!(inlineCAB)) {
-		return genSpecialSelectorSend();
-	}
-	targetBytecodePC = (branchPC + ((branchDescriptor->numBytes))) + (spanForatbyte0in(branchDescriptor, branchPC, branchBytecode, methodObj));
-	postBranchPC = branchPC + ((branchDescriptor->numBytes));
-	if (argIsInt) {
-		ssFlushTo(simStackPtr - 2);
-		popToReg(ssValue(1), ReceiverResultReg);
-		ssPop(2);
-		gMoveRR(ReceiverResultReg, TempReg);
-	}
-	else {
-		marshallSendArguments(1);
-		gMoveRR(Arg0Reg, TempReg);
-		if (!(rcvrIsInt)) {
-			if (isSmallIntegerTagNonZero()) {
-				gAndRR(ReceiverResultReg, TempReg);
-			}
-			else {
-				gOrRR(ReceiverResultReg, TempReg);
-			}
-		}
-	}
-	jumpNotSmallInts = genJumpNotSmallIntegerInScratchReg(TempReg);
-	if (argIsInt) {
-		gCmpCqR(argInt, ReceiverResultReg);
-	}
-	else {
-		gCmpRR(Arg0Reg, ReceiverResultReg);
-	}
-	genoperand(((branchDescriptor->isBranchTrue)
-		? (primDescriptor->opcode)
-		: inverseBranchFor((primDescriptor->opcode))), ((usqInt)(ensureNonMergeFixupAt(targetBytecodePC - initialPC))));
-	gJump(ensureNonMergeFixupAt(postBranchPC - initialPC));
-	jmpTarget(jumpNotSmallInts, gLabel());
-	if (argIsInt) {
-		gMoveCqR(argInt, Arg0Reg);
-	}
-	return genMarshalledSendnumArgs(specialSelector(byte0 - 176), 1);
-}
-
-static sqInt
 genSpecialSelectorEqualsEquals(void)
 {
-    sqInt argReg;
-    sqInt branchBytecode;
-    BytecodeDescriptor *branchDescriptor;
-    AbstractInstruction *jumpEqual;
     AbstractInstruction *jumpNotEqual;
-    sqInt nextPC;
-    sqInt postBranchPC;
-    BytecodeDescriptor *primDescriptor;
-    sqInt rcvrReg;
-    sqInt resultReg;
-    sqInt targetBytecodePC;
+    AbstractInstruction *jumpPush;
 
-	ssPop(2);
-	resultReg = availableRegisterOrNil();
-	if (!(resultReg)) {
-		ssAllocateRequiredReg(resultReg = Arg1Reg);
-	}
-	ssPush(2);
-	if ((((ssTop()->type)) == SSConstant)
-	 && (!((ssTop()->spilled)))) {
-		if (((ssValue(1)->type)) == SSRegister) {
-
-			/* if spilled we must generate a real pop */
-
-			rcvrReg = (ssValue(1)->registerr);
-		}
-		else {
-			popToReg(ssValue(1), rcvrReg = resultReg);
-		}
-		if (shouldAnnotateObjectReference((ssTop()->constant))) {
-			annotateobjRef(gCmpCwR((ssTop()->constant), rcvrReg), (ssTop()->constant));
-		}
-		else {
-			gCmpCqR((ssTop()->constant), rcvrReg);
-		}
-		ssPop(1);
-	}
-	else {
-		argReg = ssStorePoptoPreferredReg(1, TempReg);
-		rcvrReg = (argReg == resultReg
-			? TempReg
-			: resultReg);
-		popToReg(ssTop(), rcvrReg);
-		gCmpRR(argReg, rcvrReg);
-	}
-	ssPop(1);
-	ssPushRegister(resultReg);
-	primDescriptor = generatorAt(byte0);
-	nextPC = bytecodePointer + ((primDescriptor->numBytes));
-	branchBytecode = fetchByteofObject(nextPC, methodObj);
-	branchDescriptor = generatorAt(branchBytecode);
-	if (((branchDescriptor->isBranchTrue))
-	 || ((branchDescriptor->isBranchFalse))) {
-		ssFlushTo(simStackPtr - 1);
-		targetBytecodePC = (nextPC + ((branchDescriptor->numBytes))) + (spanForatbyte0in(branchDescriptor, nextPC, branchBytecode, methodObj));
-		postBranchPC = nextPC + ((branchDescriptor->numBytes));
-		genoperand(((branchDescriptor->isBranchTrue)
-			? JumpZero
-			: JumpNonZero), ((usqInt)(ensureNonMergeFixupAt(targetBytecodePC - initialPC))));
-		gJump(ensureNonMergeFixupAt(postBranchPC - initialPC));
-	}
-	else {
-		jumpNotEqual = gJumpNonZero(0);
-		annotateobjRef(gMoveCwR(trueObject(), resultReg), trueObject());
-		jumpEqual = gJump(0);
-		jmpTarget(jumpNotEqual, annotateobjRef(gMoveCwR(falseObject(), resultReg), falseObject()));
-		jmpTarget(jumpEqual, gLabel());
-	}
-	if (resultReg == ReceiverResultReg) {
-		(optStatus.isReceiverResultRegLive = 0);
-	}
+	gPopR(TempReg);
+	gMoveMwrR(0, SPReg, ClassReg);
+	gCmpRR(TempReg, ClassReg);
+	jumpNotEqual = gJumpNonZero(0);
+	annotateobjRef(gMoveCwR(trueObject(), TempReg), trueObject());
+	jumpPush = gJump(0);
+	jmpTarget(jumpNotEqual, annotateobjRef(gMoveCwR(falseObject(), TempReg), falseObject()));
+	jmpTarget(jumpPush, gMoveRMwr(TempReg, 0, SPReg));
 	return 0;
 }
 
@@ -10441,12 +9618,6 @@
 }
 
 static sqInt
-genSSPushSlotreg(sqInt index, sqInt baseReg)
-{
-	return ssPushBaseoffset(baseReg, slotOffsetOfInstVarIndex(index));
-}
-
-static sqInt
 genStoreAndPopReceiverVariableBytecode(void)
 {
 	return genStorePopReceiverVariable(1, byte0 & 7);
@@ -10474,57 +9645,23 @@
 }
 
 static sqInt
-genStoreImmediateInSourceRegslotIndexdestReg(sqInt sourceReg, sqInt index, sqInt destReg)
-{
-	gMoveRMwr(sourceReg, (index * BytesPerWord) + BaseHeaderSize, destReg);
-	return 0;
-}
-
-static sqInt
 genStorePopLiteralVariable(sqInt popBoolean, sqInt litVarIndex)
 {
     sqInt association;
-    sqInt constVal;
-    sqInt topReg;
-    sqInt valueReg;
 
-	flag("with better register allocation this wouldn't need a frame.  e.g. use SendNumArgs instead of ReceiverResultReg");
 	assert(needsFrame);
 	association = literalofMethod(litVarIndex, methodObj);
-	(optStatus.isReceiverResultRegLive = 0);
-	if ((((ssTop()->type)) == SSConstant)
-	 && (isImmediate((ssTop()->constant)))) {
-		constVal = (ssTop()->constant);
-		if (popBoolean) {
-			ssPop(1);
-		}
-		ssAllocateRequiredReg(ReceiverResultReg);
-		annotateobjRef(gMoveCwR(association, ReceiverResultReg), association);
-		gMoveCqR(constVal, TempReg);
-		if (traceStores > 0) {
-			CallRT(ceTraceStoreTrampoline);
-		}
-		return genStoreImmediateInSourceRegslotIndexdestReg(TempReg, ValueIndex, ReceiverResultReg);
+	annotateobjRef(gMoveCwR(association, ReceiverResultReg), association);
+	if (popBoolean) {
+		gPopR(ClassReg);
 	}
-	if ((((topReg = registerOrNil(ssTop()))) == null)
-	 || (topReg == ReceiverResultReg)) {
-		topReg = ClassReg;
+	else {
+		gMoveMwrR(0, SPReg, ClassReg);
 	}
-	ssPop(1);
-	ssAllocateRequiredReg(topReg);
-	ssPush(1);
-	flag("but what if we don't pop?  The top reg is still potentially trashed in the call;. think this through");
-	valueReg = ssStorePoptoPreferredReg(popBoolean, topReg);
-	if (valueReg == ReceiverResultReg) {
-		gMoveRR(valueReg, topReg);
-	}
-	ssAllocateCallReg(ReceiverResultReg);
-	annotateobjRef(gMoveCwR(association, ReceiverResultReg), association);
 	if (traceStores > 0) {
-		gMoveRR(topReg, TempReg);
 		CallRT(ceTraceStoreTrampoline);
 	}
-	return genStoreSourceRegslotIndexdestRegscratchReg(topReg, ValueIndex, ReceiverResultReg, TempReg);
+	return genStoreSourceRegslotIndexdestRegscratchReg(ClassReg, ValueIndex, ReceiverResultReg, TempReg);
 }
 
 static sqInt
@@ -10534,28 +9671,21 @@
     AbstractInstruction *jmpSingle;
 
 	assert(needsFrame);
-	ssFlushUpThroughReceiverVariable(slotIndex);
-	ensureReceiverResultRegContainsSelf();
-	ssPop(1);
-	ssAllocateCallRegand(ClassReg, SendNumArgsReg);
-	ssPush(1);
+	gMoveMwrR(FoxMFReceiver, FPReg, ReceiverResultReg);
 	genLoadSlotsourceRegdestReg(SenderIndex, ReceiverResultReg, TempReg);
-	flag("why do we always pop??");
-	flag("but what if we don't pop?  The top reg is still potentially trashed in the call;. think this through");
-	popToReg(ssTop(), ClassReg);
+	gMoveMwrR(0, SPReg, ClassReg);
 	jmpSingle = genJumpNotSmallIntegerInScratchReg(TempReg);
 	gMoveCqR(slotIndex, SendNumArgsReg);
 	CallRT(ceStoreContextInstVarTrampoline);
 	jmpDone = gJump(0);
 	jmpTarget(jmpSingle, gLabel());
 	if (traceStores > 0) {
-		gMoveRR(ClassReg, TempReg);
 		CallRT(ceTraceStoreTrampoline);
 	}
 	genStoreSourceRegslotIndexdestRegscratchReg(ClassReg, slotIndex, ReceiverResultReg, TempReg);
 	jmpTarget(jmpDone, gLabel());
 	if (popBoolean) {
-		ssPop(1);
+		gAddCqR(BytesPerWord, SPReg);
 	}
 	return 0;
 }
@@ -10563,100 +9693,48 @@
 static sqInt
 genStorePopReceiverVariable(sqInt popBoolean, sqInt slotIndex)
 {
-    sqInt constVal;
-    sqInt topReg;
-    sqInt valueReg;
-
-	ssFlushUpThroughReceiverVariable(slotIndex);
-	if ((((ssTop()->type)) == SSConstant)
-	 && (isImmediate((ssTop()->constant)))) {
-		constVal = (ssTop()->constant);
-		if (popBoolean) {
-			ssPop(1);
-		}
-		ensureReceiverResultRegContainsSelf();
-		gMoveCqR(constVal, TempReg);
-		if (traceStores > 0) {
-			CallRT(ceTraceStoreTrampoline);
-		}
-		return genStoreImmediateInSourceRegslotIndexdestReg(TempReg, slotIndex, ReceiverResultReg);
+	if (needsFrame) {
+		gMoveMwrR(FoxMFReceiver, FPReg, ReceiverResultReg);
 	}
-	if ((((topReg = registerOrNil(ssTop()))) == null)
-	 || (topReg == ReceiverResultReg)) {
-		topReg = ClassReg;
+	if (popBoolean) {
+		gPopR(ClassReg);
 	}
-	ssPop(1);
-	ssAllocateCallReg(topReg);
-	ssPush(1);
-	flag("but what if we don't pop?  The top reg is still potentially trashed in the call;. think this through");
-	valueReg = ssStorePoptoPreferredReg(popBoolean, topReg);
-	if (valueReg == ReceiverResultReg) {
-		gMoveRR(valueReg, topReg);
+	else {
+		gMoveMwrR(0, SPReg, ClassReg);
 	}
-	ensureReceiverResultRegContainsSelf();
 	if (traceStores > 0) {
-		gMoveRR(topReg, TempReg);
 		CallRT(ceTraceStoreTrampoline);
 	}
-	return genStoreSourceRegslotIndexdestRegscratchReg(topReg, slotIndex, ReceiverResultReg, TempReg);
+	return genStoreSourceRegslotIndexdestRegscratchReg(ClassReg, slotIndex, ReceiverResultReg, TempReg);
 }
 
 static sqInt
 genStorePopRemoteTempAt(sqInt popBoolean, sqInt slotIndex, sqInt remoteTempIndex)
 {
-    sqInt constVal;
-    sqInt topReg;
-    sqInt valueReg;
-
 	assert(needsFrame);
-	(optStatus.isReceiverResultRegLive = 0);
-	if ((((ssTop()->type)) == SSConstant)
-	 && (isImmediate((ssTop()->constant)))) {
-		constVal = (ssTop()->constant);
-		if (popBoolean) {
-			ssPop(1);
-		}
-		ssAllocateRequiredReg(ReceiverResultReg);
-		gMoveMwrR(frameOffsetOfTemporary(remoteTempIndex), FPReg, ReceiverResultReg);
-		gMoveCqR(constVal, TempReg);
-		if (traceStores > 0) {
-			CallRT(ceTraceStoreTrampoline);
-		}
-		return genStoreImmediateInSourceRegslotIndexdestReg(TempReg, slotIndex, ReceiverResultReg);
+	if (popBoolean) {
+		gPopR(ClassReg);
 	}
-	if ((((topReg = registerOrNil(ssTop()))) == null)
-	 || (topReg == ReceiverResultReg)) {
-		topReg = ClassReg;
+	else {
+		gMoveMwrR(0, SPReg, ClassReg);
 	}
-	ssPop(1);
-	ssAllocateRequiredReg(topReg);
-	ssPush(1);
-	flag("but what if we don't pop?  The top reg is still potentially trashed in the call;. think this through");
-	valueReg = ssStorePoptoPreferredReg(popBoolean, topReg);
-	if (valueReg == ReceiverResultReg) {
-		gMoveRR(valueReg, topReg);
-	}
-	if (!(popBoolean)) {
-		ssPop(1);
-		ssPushRegister(topReg);
-	}
-	ssAllocateCallReg(ReceiverResultReg);
 	gMoveMwrR(frameOffsetOfTemporary(remoteTempIndex), FPReg, ReceiverResultReg);
 	if (traceStores > 0) {
-		gMoveRR(topReg, TempReg);
 		CallRT(ceTraceStoreTrampoline);
 	}
-	return genStoreSourceRegslotIndexdestRegscratchReg(topReg, slotIndex, ReceiverResultReg, TempReg);
+	return genStoreSourceRegslotIndexdestRegscratchReg(ClassReg, slotIndex, ReceiverResultReg, TempReg);
 }
 
 static sqInt
 genStorePopTemporaryVariable(sqInt popBoolean, sqInt tempIndex)
 {
-    sqInt reg;
-
-	ssFlushUpThroughTemporaryVariable(tempIndex);
-	reg = ssStorePoptoPreferredReg(popBoolean, TempReg);
-	gMoveRMwr(reg, frameOffsetOfTemporary(tempIndex), FPReg);
+	if (popBoolean) {
+		gPopR(TempReg);
+	}
+	else {
+		gMoveMwrR(0, SPReg, TempReg);
+	}
+	gMoveRMwr(TempReg, frameOffsetOfTemporary(tempIndex), FPReg);
 	return 0;
 }
 
@@ -10749,6 +9827,28 @@
 }
 
 
+/*	Generate a trampoline with two arguments.
+	Hack: a negative value indicates an abstract register, a non-negative
+	value indicates a constant. */
+
+static sqInt
+genTrampolineForcalledargarg(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1)
+{
+	return genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(aRoutine, aString, 1, 2, regOrConst0, regOrConst1, null, null, 0, null, 0);
+}
+
+
+/*	Generate a trampoline with four arguments.
+	Hack: a negative value indicates an abstract register, a non-negative
+	value indicates a constant. */
+
+static sqInt
+genTrampolineForcalledargargargarg(void *aRoutine, char *aString, sqInt regOrConst0, sqInt regOrConst1, sqInt regOrConst2, sqInt regOrConst3)
+{
+	return genTrampolineForcalledcallJumpBarnumArgsargargargargsaveRegsresultRegappendOpcodes(aRoutine, aString, 1, 4, regOrConst0, regOrConst1, regOrConst2, regOrConst3, 0, null, 0);
+}
+
+
 /*	Generate a trampoline with two arguments that answers a result.
 	Hack: a negative value indicates an abstract register, a non-negative
 	value indicates a constant. */
@@ -10818,6 +9918,7 @@
 static sqInt
 genUpArrowReturn(void)
 {
+	flag("currently caller pushes result");
 	if (inBlock) {
 		assert(needsFrame);
 		annotateBytecode(CallRT(ceNonLocalReturnTrampoline));
@@ -10826,14 +9927,8 @@
 	if (needsFrame) {
 		gMoveRR(FPReg, SPReg);
 		gPopR(FPReg);
-		gRetN((methodOrBlockNumArgs + 1) * BytesPerWord);
 	}
-	else {
-		gRetN(((methodOrBlockNumArgs > (numRegArgs()))
-		 || (regArgsHaveBeenPushed)
-			? (methodOrBlockNumArgs + 1) * BytesPerWord
-			: 0));
-	}
+	gRetN((methodOrBlockNumArgs + 1) * BytesPerWord);
 	return 0;
 }
 
@@ -11059,7 +10154,6 @@
 	(methodLabel->opcode = Label);
 	((methodLabel->operands))[0] = 0;
 	((methodLabel->operands))[1] = 0;
-	callerSavedRegMask = callerSavedRegisterMask(backEnd);
 }
 
 void
@@ -11084,9 +10178,6 @@
 
 /*	Make sure there's a flagged fixup at the targetIndex (pc relative to first
 	pc) in fixups.
-	These are the targets of backward branches. A backward branch fixup's
-	simStackPtr needs to be set when generating the code for the bytecode at
-	the targetIndex.
 	Initially a fixup's target is just a flag. Later on it is replaced with a
 	proper instruction. */
 
@@ -11096,8 +10187,7 @@
     BytecodeFixup *fixup;
 
 	fixup = fixupAt(targetIndex);
-	(fixup->targetInstruction = ((AbstractInstruction *) 2));
-	(fixup->simStackPtr = -2);
+	(fixup->targetInstruction = ((AbstractInstruction *) 1));
 	return fixup;
 }
 
@@ -11128,73 +10218,7 @@
 	return 3;
 }
 
-static void
-initSimStackForFramefulMethod(sqInt startpc)
-{
-    CogSimStackEntry *desc;
-    sqInt i;
 
-	(optStatus.isReceiverResultRegLive = 0);
-	(simSelf.type = SSBaseOffset);
-	(simSelf.registerr = FPReg);
-	(simSelf.offset = FoxMFReceiver);
-	(simSelf.spilled = 1);
-
-	/* N.B. Includes num args */
-
-	simSpillBase = methodOrBlockNumTemps;
-
-	/* args */
-
-	simStackPtr = simSpillBase - 1;
-	for (i = 0; i <= (methodOrBlockNumArgs - 1); i += 1) {
-		desc = simStackAt(i);
-		(desc->type = SSBaseOffset);
-		(desc->registerr = FPReg);
-		(desc->offset = FoxCallerSavedIP + ((methodOrBlockNumArgs - i) * BytesPerWord));
-		(desc->spilled = 1);
-		(desc->bcptr = startpc);
-	}
-	for (i = methodOrBlockNumArgs; i <= simStackPtr; i += 1) {
-		desc = simStackAt(i);
-		(desc->type = SSBaseOffset);
-		(desc->registerr = FPReg);
-		(desc->offset = FoxMFReceiver - (((i - methodOrBlockNumArgs) + 1) * BytesPerWord));
-		(desc->spilled = 1);
-		(desc->bcptr = startpc);
-	}
-}
-
-static void
-initSimStackForFramelessMethod(sqInt startpc)
-{
-    CogSimStackEntry *desc;
-
-	(simSelf.type = SSRegister);
-	(simSelf.registerr = ReceiverResultReg);
-	(simSelf.spilled = 0);
-	(optStatus.isReceiverResultRegLive = 1);
-	(optStatus.ssEntry = (&simSelf));
-	assert(methodOrBlockNumTemps == methodOrBlockNumArgs);
-	simStackPtr = simSpillBase = -1;
-	assert((numRegArgs()) <= 2);
-	if (((methodOrBlockNumArgs >= 1) && (methodOrBlockNumArgs <= (numRegArgs())))) {
-		desc = simStackAt(0);
-		(desc->type = SSRegister);
-		(desc->registerr = Arg0Reg);
-		(desc->spilled = 0);
-		(desc->bcptr = startpc);
-		if (methodOrBlockNumArgs > 1) {
-			desc = simStackAt(1);
-			(desc->type = SSRegister);
-			(desc->registerr = Arg1Reg);
-			(desc->spilled = 0);
-			(desc->bcptr = startpc);
-		}
-	}
-}
-
-
 /*	Answer the inline cache tag for the return address of a send. */
 
 static sqInt
@@ -11287,72 +10311,6 @@
 }
 
 static sqInt
-inverseBranchFor(sqInt opcode)
-{
-	
-	switch (opcode) {
-	case JumpLongZero:
-				return JumpLongNonZero;
-
-	case JumpLongNonZero:
-				return JumpLongZero;
-
-	case JumpZero:
-				return JumpNonZero;
-
-	case JumpNonZero:
-				return JumpZero;
-
-	case JumpNegative:
-				return JumpNonNegative;
-
-	case JumpNonNegative:
-				return JumpNegative;
-
-	case JumpOverflow:
-				return JumpNoOverflow;
-
-	case JumpNoOverflow:
-				return JumpOverflow;
-
-	case JumpCarry:
-				return JumpNoCarry;
-
-	case JumpNoCarry:
-				return JumpCarry;
-
-	case JumpLess:
-				return JumpGreaterOrEqual;
-
-	case JumpGreaterOrEqual:
-				return JumpLess;
-
-	case JumpGreater:
-				return JumpLessOrEqual;
-
-	case JumpLessOrEqual:
-				return JumpGreater;
-
-	case JumpBelow:
-				return JumpAboveOrEqual;
-
-	case JumpAboveOrEqual:
-				return JumpBelow;
-
-	case JumpAbove:
-				return JumpBelowOrEqual;
-
-	case JumpBelowOrEqual:
-				return JumpAbove;
-
-	default:
-		error("Case not found and no otherwise clause");
-	}
-	error("invalid opcode for inverse");
-	return 0;
-}
-
-static sqInt
 isAFixup(AbstractInstruction * self_in_isAFixup, void *fixupOrAddress)
 {
 	return addressIsInFixups(fixupOrAddress);
@@ -11438,12 +10396,6 @@
 	 || (((target >= methodZoneBase) && (target <= (zoneLimit()))));
 }
 
-static sqInt
-isSmallIntegerTagNonZero(void)
-{
-	return 1;
-}
-
 static AbstractInstruction *
 gJumpAboveOrEqual(void *jumpTarget)
 {
@@ -11551,12 +10503,6 @@
 }
 
 static AbstractInstruction *
-gJumpNoOverflow(void *jumpTarget)
-{
-	return genoperand(JumpNoOverflow, ((sqInt)jumpTarget));
-}
-
-static AbstractInstruction *
 gJumpOverflow(void *jumpTarget)
 {
 	return genoperand(JumpOverflow, ((sqInt)jumpTarget));
@@ -11782,20 +10728,7 @@
 	return ((((byteAt(followingAddress - 1)) << 24) + ((byteAt(followingAddress - 2)) << 16)) + ((byteAt(followingAddress - 3)) << 8)) + (byteAt(followingAddress - 4));
 }
 
-static sqInt
-liveRegisters(void)
-{
-    sqInt i;
-    sqInt regsSet;
 
-	regsSet = 0;
-	for (i = (((simSpillBase < 0) ? 0 : simSpillBase)); i <= simStackPtr; i += 1) {
-		regsSet = regsSet | (registerMask(simStackAt(i)));
-	}
-	return regsSet;
-}
-
-
 /*	Answer the byte size of a MoveCwR opcode's corresponding machine code */
 
 static sqInt
@@ -12000,6 +10933,10 @@
 		homeMethod = ((CogMethod *) cogMethod);
 		assert(startbcpc == (startPCOfMethodHeader((homeMethod->methodHeader))));
 		map = findMapLocationForMcpcinMethod(mcpc, homeMethod);
+		assert(map != 0);
+		if (map == 0) {
+			return 0;
+		}
 		assert(((((usqInt) (byteAt(map))) >> AnnotationShift) == IsMethodReference)
 		 || (((((usqInt) (byteAt(map))) >> AnnotationShift) == IsRelativeCall)
  || ((((usqInt) (byteAt(map))) >> AnnotationShift) == IsDisplacementX2N)));
@@ -12009,6 +10946,10 @@
 		mcpc = (((sqInt)cogMethod)) + (sizeof(CogBlockMethod));
 		homeMethod = cogHomeMethod(cogMethod);
 		map = findMapLocationForMcpcinMethod(mcpc, homeMethod);
+		assert(map != 0);
+		if (map == 0) {
+			return 0;
+		}
 		assert(((((usqInt) (byteAt(map))) >> AnnotationShift) == HasBytecodePC)
 		 || ((((usqInt) (byteAt(map))) >> AnnotationShift) == IsDisplacementX2N));
 		while ((((usqInt) (byteAt(map))) >> AnnotationShift) != HasBytecodePC) {
@@ -12489,45 +11430,6 @@
 	return 0;
 }
 
-
-/*	Spill everything on the simulated stack that needs spilling (that below
-	receiver and arguments).
-	Marshall receiver and arguments to stack and/or registers depending on arg
-	count. If the args don't fit in registers push receiver and args (spill
-	everything), but still assign
-	the receiver to ReceiverResultReg. */
-
-static void
-marshallSendArguments(sqInt numArgs)
-{
-	if (numArgs > (numRegArgs())) {
-		ssFlushTo(simStackPtr);
-		storeToReg(simStackAt(simStackPtr - numArgs), ReceiverResultReg);
-	}
-	else {
-		ssFlushTo((simStackPtr - numArgs) - 1);
-		if (numArgs > 0) {
-			if (((numRegArgs()) > 1)
-			 && (numArgs > 1)) {
-				ssAllocateRequiredRegupThrough(Arg0Reg, simStackPtr - 2);
-				ssAllocateRequiredRegupThrough(Arg1Reg, simStackPtr - 1);
-			}
-			else {
-				ssAllocateRequiredRegupThrough(Arg0Reg, simStackPtr - 1);
-			}
-		}
-		if (((numRegArgs()) > 1)
-		 && (numArgs > 1)) {
-			popToReg(simStackAt(simStackPtr), Arg1Reg);
-		}
-		if (numArgs > 0) {
-			popToReg(simStackAt((simStackPtr - numArgs) + 1), Arg0Reg);
-		}
-		popToReg(simStackAt(simStackPtr - numArgs), ReceiverResultReg);
-	}
-	ssPop(numArgs + 1);
-}
-
 usqInt
 maxCogMethodAddress(void)
 {
@@ -12607,64 +11509,10 @@
 		: absPC);
 }
 
-
-/*	Discard type information because of a control-flow merge. */
-
-static void
-mergeAtfrom(CogSimStackEntry * self_in_mergeAtfrom, sqInt baseOffset, sqInt baseRegister)
-{
-	assert((self_in_mergeAtfrom->spilled));
-	if (((self_in_mergeAtfrom->type)) == SSSpill) {
-		assert((((self_in_mergeAtfrom->offset)) == baseOffset)
-		 && (((self_in_mergeAtfrom->registerr)) == baseRegister));
-	}
-	else {
-		(self_in_mergeAtfrom->type) = SSSpill;
-		(self_in_mergeAtfrom->offset) = baseOffset;
-		(self_in_mergeAtfrom->registerr) = baseRegister;
-	}
-}
-
-
-/*	Merge control flow at a fixup. The fixup holds the simStackPtr at the jump
-	to this target.
-	See stackToRegisterMapping on the class side for a full description. */
-
-static void
-mergeafterReturn(BytecodeFixup *fixup, sqInt mergeFollowsReturn)
-{
-    sqInt i;
-
-	traceMerge(fixup);
-	(optStatus.isReceiverResultRegLive = 0);
-	if (mergeFollowsReturn) {
-		assert((((usqInt)((fixup->targetInstruction)))) >= 2);
-		simStackPtr = (fixup->simStackPtr);
-	}
-	if ((((usqInt)((fixup->targetInstruction)))) <= 2) {
-		ssFlushTo(simStackPtr);
-		if (((fixup->simStackPtr)) <= -2) {
-			(fixup->simStackPtr = simStackPtr);
-		}
-		(fixup->targetInstruction = gLabel());
-	}
-	assert(simStackPtr >= ((fixup->simStackPtr)));
-	;
-	simStackPtr = (fixup->simStackPtr);
-
-	/* For now throw away all type information for values on the stack, but sometime consider
-	 the more sophisticated merge described in the class side stackToRegisterMapping. */
-
-	simSpillBase = methodOrBlockNumTemps;
-	for (i = methodOrBlockNumTemps; i <= simStackPtr; i += 1) {
-		mergeAtfrom(simStackAt(i), FoxMFReceiver - (((i - methodOrBlockNumArgs) + 1) * BytesPerOop), FPReg);
-	}
-}
-
 static sqInt
 methodAbortTrampolineFor(sqInt numArgs)
 {
-	return methodAbortTrampolines[((numArgs < ((numRegArgs()) + 1)) ? numArgs : ((numRegArgs()) + 1))];
+	return ceMethodAbortTrampoline;
 }
 
 static CogMethod *
@@ -12719,13 +11567,7 @@
 	return genoperand(NegateR, reg);
 }
 
-static AbstractInstruction *
-gNop(void)
-{
-	return gen(Nop);
-}
 
-
 /*	Compute the distance to the logically subsequent bytecode, i.e. skip over
 	blocks. 
  */
@@ -13052,7 +11894,7 @@
 static sqInt
 picAbortTrampolineFor(sqInt numArgs)
 {
-	return picAbortTrampolines[((numArgs < ((numRegArgs()) + 1)) ? numArgs : ((numRegArgs()) + 1))];
+	return cePICAbortTrampoline;
 }
 
 
@@ -13080,37 +11922,7 @@
 	}
 }
 
-static void
-popToReg(CogSimStackEntry * self_in_popToReg, sqInt reg)
-{
-	if ((self_in_popToReg->spilled)) {
-		gPopR(reg);
-		return;
-	}
-	
-	switch ((self_in_popToReg->type)) {
-	case SSBaseOffset:
-				gMoveMwrR((self_in_popToReg->offset), (self_in_popToReg->registerr), reg);
-		break;
-	case SSConstant:
-				if (shouldAnnotateObjectReference((self_in_popToReg->constant))) {
-			annotateobjRef(gMoveCwR((self_in_popToReg->constant), reg), (self_in_popToReg->constant));
-		}
-		else {
-			gMoveCqR((self_in_popToReg->constant), reg);
-		}
-		break;
-	case SSRegister:
-				if (reg != ((self_in_popToReg->registerr))) {
-			gMoveRR((self_in_popToReg->registerr), reg);
-		}
-		break;
-	default:
-		error("Case not found and no otherwise clause");
-	}
-}
 
-
 /*	If there is a generator for the current primitive then answer it;
 	otherwise answer nil. */
 
@@ -13298,45 +12110,15 @@
 }
 
 
-/*	Answer a bit mask for the receiver's register, if any. */
+/*	Dummy implementation for CogFooCompiler>callerSavedRegisterMask
+	which doesn't get pruned due to Slang limitations. */
 
 static sqInt
-registerMask(CogSimStackEntry * self_in_registerMask)
-{
-	return ((((self_in_registerMask->type)) == SSBaseOffset)
-	 || (((self_in_registerMask->type)) == SSRegister)
-		? registerMaskFor((self_in_registerMask->registerr))
-		: 0);
-}
-
-
-/*	Answer a bit mask identifying the symbolic register.
-	Registers are negative numbers. */
-
-static sqInt
-registerMaskFor(sqInt reg)
-{
-	return (((1 - reg) < 0) ? ((usqInt) 1 >> -(1 - reg)) : ((usqInt) 1 << (1 - reg)));
-}
-
-
-/*	Answer a bit mask identifying the symbolic registers.
-	Registers are negative numbers. */
-
-static sqInt
 registerMaskForandand(sqInt reg1, sqInt reg2, sqInt reg3)
 {
-	return (((((1 - reg1) < 0) ? ((usqInt) 1 >> -(1 - reg1)) : ((usqInt) 1 << (1 - reg1)))) | ((((1 - reg2) < 0) ? ((usqInt) 1 >> -(1 - reg2)) : ((usqInt) 1 << (1 - reg2))))) | ((((1 - reg3) < 0) ? ((usqInt) 1 >> -(1 - reg3)) : ((usqInt) 1 << (1 - reg3))));
+	return 0;
 }
 
-static sqInt
-registerOrNil(CogSimStackEntry * self_in_registerOrNil)
-{
-	return (((self_in_registerOrNil->type)) == SSRegister
-		? (self_in_registerOrNil->registerr)
-		: 0);
-}
-
 static void
 relocateAndPruneYoungReferrers(void)
 {
@@ -13629,21 +12411,12 @@
 }
 
 
-/*	We must ensure the ReceiverResultReg is live across the store check so
-	that we can store into receiver inst vars in a frameless method since self
-	exists only in ReceiverResultReg in a frameless method. So if
-	ReceiverResultReg is
-	caller-saved we use the fact that ceStoreCheck: answers its argument to
-	reload ReceiverResultReg cheaply. Otherwise we don't care about the result
-	and use the cResultRegister, effectively a no-op (see
-	compileTrampoline...)  */
+/*	See the subclass for explanation. */
 
 static sqInt
 returnRegForStoreCheck(void)
 {
-	return ((registerMaskFor(ReceiverResultReg)) & callerSavedRegMask
-		? ReceiverResultReg
-		: cResultRegister(backEnd));
+	return cResultRegister(backEnd);
 }
 
 
@@ -13789,7 +12562,6 @@
     BytecodeDescriptor *descriptor;
     sqInt end;
     sqInt pc;
-    sqInt pushingNils;
     sqInt stackDelta;
 
 	needsFrame = 0;
@@ -13797,8 +12569,6 @@
 	pc = (blockStart->startpc);
 	end = ((blockStart->startpc)) + ((blockStart->span));
 	stackDelta = 0;
-	pushingNils = 1;
-	(blockStart->numInitialNils = 0);
 	while (pc < end) {
 		byte0 = fetchByteofObject(pc, methodObj);
 		descriptor = generatorAt(byte0);
@@ -13810,20 +12580,12 @@
 				stackDelta += (descriptor->stackDelta);
 			}
 		}
-		if (pushingNils) {
-			if ((pushingNils = (((descriptor->generator)) == (genPushConstantNilBytecode))
-			 && (((fixupAt(pc - initialPC)->targetInstruction)) == 0))) {
-				assert(((descriptor->numBytes)) == 1);
-				(blockStart->numInitialNils = ((blockStart->numInitialNils)) + 1);
-			}
-		}
 		pc = nextBytecodePCForatbyte0in(descriptor, pc, byte0, methodObj);
 	}
 	if (!(needsFrame)) {
 		if (stackDelta < 0) {
 			error("negative stack delta in block; block contains bogus code or internal error");
 		}
-		(blockStart->numInitialNils = 0);
 		while (stackDelta > 0) {
 			descriptor = generatorAt(fetchByteofObject((blockStart->startpc), methodObj));
 			if (((descriptor->generator)) != (genPushConstantNilBytecode)) {
@@ -14146,289 +12908,7 @@
 	}
 }
 
-static void
-ssAllocateCallReg(sqInt requiredReg1)
-{
-	ssAllocateRequiredRegMaskupThrough(callerSavedRegMask | (registerMaskFor(requiredReg1)), simStackPtr);
-}
-
-static void
-ssAllocateCallRegand(sqInt requiredReg1, sqInt requiredReg2)
-{
-	ssAllocateRequiredRegMaskupThrough(callerSavedRegMask | ((registerMaskFor(requiredReg1)) | (registerMaskFor(requiredReg2))), simStackPtr);
-}
-
 static sqInt
-ssAllocatePreferredReg(sqInt preferredReg)
-{
-    sqInt i;
-    sqInt lastPreferred;
-    sqInt liveRegs;
-    sqInt preferredMask;
-    sqInt reg;
-
-
-	/* compute live regs while noting the last occurrence of preferredReg.
-	 If there are none free we must spill from simSpillBase to last occurrence. */
-
-	lastPreferred = -1;
-	preferredMask = registerMaskFor(preferredReg);
-	liveRegs = registerMaskForandand(TempReg, FPReg, SPReg);
-	for (i = (((simSpillBase < 0) ? 0 : simSpillBase)); i <= simStackPtr; i += 1) {
-		liveRegs = liveRegs | (registerMask(simStackAt(i)));
-		if ((liveRegs & preferredMask) != 0) {
-			lastPreferred = i;
-		}
-	}
-	if ((liveRegs & (registerMaskFor(preferredReg))) == 0) {
-		return preferredReg;
-	}
-	for (reg = GPRegMin; reg <= GPRegMax; reg += 1) {
-		if ((liveRegs & (registerMaskFor(reg))) == 0) {
-			return reg;
-		}
-	}
-	ssFlushTo(lastPreferred);
-	assert(((liveRegisters()) & preferredMask) == 0);
-	return preferredReg;
-}
-
-static void
-ssAllocateRequiredRegMaskupThrough(sqInt requiredRegsMask, sqInt stackPtr)
-{
-    sqInt i;
-    sqInt lastRequired;
-    sqInt liveRegs;
-
-
-	/* compute live regs while noting the last occurrence of required regs.
-	 If these are not free we must spill from simSpillBase to last occurrence.
-	 Note we are conservative here; we could allocate FPReg in frameless methods. */
-
-	lastRequired = -1;
-	liveRegs = registerMaskForandand(TempReg, FPReg, SPReg);
-	for (i = (((simSpillBase < 0) ? 0 : simSpillBase)); i <= stackPtr; i += 1) {
-		liveRegs = liveRegs | (registerMask(simStackAt(i)));
-		if ((liveRegs & requiredRegsMask) != 0) {
-			lastRequired = i;
-		}
-	}
-	if (!((liveRegs & requiredRegsMask) == 0)) {
-		ssFlushTo(lastRequired);
-		assert(((liveRegisters()) & requiredRegsMask) == 0);
-	}
-}
-
-static void
-ssAllocateRequiredReg(sqInt requiredReg)
-{
-	ssAllocateRequiredRegMaskupThrough(registerMaskFor(requiredReg), simStackPtr);
-}
-
-static void
-ssAllocateRequiredRegand(sqInt requiredReg1, sqInt requiredReg2)
-{
-	ssAllocateRequiredRegMaskupThrough((registerMaskFor(requiredReg1)) | (registerMaskFor(requiredReg2)), simStackPtr);
-}
-
-static void
-ssAllocateRequiredRegupThrough(sqInt requiredReg, sqInt stackPtr)
-{
-	ssAllocateRequiredRegMaskupThrough(registerMaskFor(requiredReg), stackPtr);
-}
-
-static void
-ssFlushTo(sqInt index)
-{
-    sqInt i;
-
-	for (i = methodOrBlockNumTemps; i <= (simSpillBase - 1); i += 1) {
-		assert((simStackAt(i)->spilled));
-	}
-	if (simSpillBase <= index) {
-		for (i = (((simSpillBase < 0) ? 0 : simSpillBase)); i <= index; i += 1) {
-			assert(needsFrame);
-			ensureSpilledAtfrom(simStackAt(i), frameOffsetOfTemporary(i), FPReg);
-		}
-		simSpillBase = index + 1;
-	}
-}
-
-
-/*	Any occurrences on the stack of the value being stored must
-	be flushed, and hence any values colder than them stack. */
-
-static void
-ssFlushUpThroughReceiverVariable(sqInt slotIndex)
-{
-    CogSimStackEntry *desc;
-    sqInt index;
-
-	for (index = simStackPtr; index >= (((simSpillBase < 0) ? 0 : simSpillBase)); index += -1) {
-		desc = simStackAt(index);
-		if ((((desc->type)) == SSBaseOffset)
-		 && ((((desc->registerr)) == ReceiverResultReg)
- && (((desc->offset)) == (slotOffsetOfInstVarIndex(slotIndex))))) {
-			ssFlushTo(index);
-			return;
-		}
-	}
-}
-
-
-/*	Any occurrences on the stack of the value being stored must
-	be flushed, and hence any values colder than them stack. */
-
-static void
-ssFlushUpThroughTemporaryVariable(sqInt tempIndex)
-{
-    CogSimStackEntry *desc;
-    sqInt index;
-
-	for (index = simStackPtr; index >= simSpillBase; index += -1) {
-		desc = simStackAt(index);
-		if ((((desc->type)) == SSBaseOffset)
-		 && ((((desc->registerr)) == FPReg)
- && (((desc->offset)) == (frameOffsetOfTemporary(tempIndex))))) {
-			ssFlushTo(index);
-			return;
-		}
-	}
-}
-
-static void
-ssPop(sqInt n)
-{
-	assert(((simStackPtr - n) >= (methodOrBlockNumTemps - 1))
-	 || ((!needsFrame)
- && ((simStackPtr - n) >= -1)));
-	simStackPtr -= n;
-}
-
-static sqInt
-ssPushBaseoffset(sqInt reg, sqInt offset)
-{
-    CogSimStackEntry * cascade0;
-
-	ssPush(1);
-	if (simSpillBase > simStackPtr) {
-		simSpillBase = ((simStackPtr < 0) ? 0 : simStackPtr);
-	}
-	cascade0 = ssTop();
-	(cascade0->type = SSBaseOffset);
-	(cascade0->registerr = reg);
-	(cascade0->offset = offset);
-	(cascade0->spilled = 0);
-	(cascade0->bcptr = bytecodePointer);
-	return 0;
-}
-
-static sqInt
-ssPushConstant(sqInt literal)
-{
-    CogSimStackEntry * cascade0;
-
-	ssPush(1);
-	if (simSpillBase > simStackPtr) {
-		simSpillBase = ((simStackPtr < 0) ? 0 : simStackPtr);
-	}
-	cascade0 = ssTop();
-	(cascade0->type = SSConstant);
-	(cascade0->constant = literal);
-	(cascade0->spilled = 0);
-	(cascade0->bcptr = bytecodePointer);
-	return 0;
-}
-
-static sqInt
-ssPushDesc(CogSimStackEntry simStackEntry)
-{
-	if (((simStackEntry.type)) == SSSpill) {
-		(simStackEntry.type = SSBaseOffset);
-	}
-	(simStackEntry.spilled = 0);
-	(simStackEntry.bcptr = bytecodePointer);
-	simStack[(simStackPtr += 1)] = simStackEntry;
-	if (simSpillBase > simStackPtr) {
-		simSpillBase = ((simStackPtr < 0) ? 0 : simStackPtr);
-	}
-	return 0;
-}
-
-static sqInt
-ssPushRegister(sqInt reg)
-{
-    CogSimStackEntry * cascade0;
-
-	ssPush(1);
-	if (simSpillBase > simStackPtr) {
-		simSpillBase = ((simStackPtr < 0) ? 0 : simStackPtr);
-	}
-	cascade0 = ssTop();
-	(cascade0->type = SSRegister);
-	(cascade0->registerr = reg);
-	(cascade0->spilled = 0);
-	(cascade0->bcptr = bytecodePointer);
-	return 0;
-}
-
-static void
-ssPush(sqInt n)
-{
-	simStackPtr += n;
-}
-
-
-/*	Store or pop the top simulated stack entry to a register.
-	Pop to preferredReg if the entry is not itself a register.
-	Answer the actual register the result ends up in. */
-
-static sqInt
-ssStorePoptoPreferredReg(sqInt popBoolean, sqInt preferredReg)
-{
-    sqInt actualReg;
-
-	actualReg = preferredReg;
-	if (popBoolean) {
-		if ((((ssTop()->type)) == SSRegister)
-		 && (!((ssTop()->spilled)))) {
-			actualReg = (ssTop()->registerr);
-		}
-		else {
-			popToReg(ssTop(), preferredReg);
-		}
-		ssPop(1);
-	}
-	else {
-		if (((ssTop()->type)) == SSRegister) {
-			actualReg = (ssTop()->registerr);
-		}
-		else {
-			storeToReg(ssTop(), preferredReg);
-		}
-	}
-	return actualReg;
-}
-
-static CogSimStackEntry *
-ssTop(void)
-{
-	return simStackAt(simStackPtr);
-}
-
-static CogSimStackEntry
-ssTopDescriptor(void)
-{
-	return simStack[simStackPtr];
-}
-
-static CogSimStackEntry *
-ssValue(sqInt n)
-{
-	return simStackAt(simStackPtr - n);
-}
-
-static sqInt
 stackBytesForNumArgs(AbstractInstruction * self_in_stackBytesForNumArgs, sqInt numArgs)
 {
 	return numArgs * 4;
@@ -14472,33 +12952,6 @@
 	byteAtput(followingAddress - 4, literal & 255);
 }
 
-static void
-storeToReg(CogSimStackEntry * self_in_storeToReg, sqInt reg)
-{
-	
-	switch ((self_in_storeToReg->type)) {
-	case SSBaseOffset:
-	case SSSpill:
-				gMoveMwrR((self_in_storeToReg->offset), (self_in_storeToReg->registerr), reg);
-		break;
-	case SSConstant:
-				if (shouldAnnotateObjectReference((self_in_storeToReg->constant))) {
-			annotateobjRef(gMoveCwR((self_in_storeToReg->constant), reg), (self_in_storeToReg->constant));
-		}
-		else {
-			gMoveCqR((self_in_storeToReg->constant), reg);
-		}
-		break;
-	case SSRegister:
-				if (reg != ((self_in_storeToReg->registerr))) {
-			gMoveRR((self_in_storeToReg->registerr), reg);
-		}
-		break;
-	default:
-		error("Case not found and no otherwise clause");
-	}
-}
-
 static sqInt
 sib(AbstractInstruction * self_in_sib, sqInt scale, sqInt indexReg, sqInt baseReg)
 {

Modified: branches/Cog/src/vm/cogit.h
===================================================================
--- branches/Cog/src/vm/cogit.h	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/src/vm/cogit.h	2011-01-01 20:18:49 UTC (rev 2337)
@@ -1,5 +1,5 @@
 /* Automatically generated by
-	CCodeGenerator VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CCodeGenerator VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
  */
 
 
@@ -11,12 +11,7 @@
 sqInt canMapBytecodePCsToNativePCs(void);
 extern void (*ceCaptureCStackPointers)();
 sqInt ceCPICMissreceiver(CogMethod *cPIC, sqInt receiver);
-extern void (*ceEnter0ArgsPIC)();
-extern void (*ceEnter1ArgsPIC)();
-extern void (*ceEnter2ArgsPIC)();
 extern void (*ceEnterCogCodePopReceiverAndClassRegs)();
-extern void (*ceEnterCogCodePopReceiverArg0Regs)();
-extern void (*ceEnterCogCodePopReceiverArg1Arg0Regs)();
 extern void (*ceEnterCogCodePopReceiverReg)();
 sqInt ceSICMiss(sqInt receiver);
 void checkAssertsEnabledInCogit(void);
@@ -31,8 +26,6 @@
 void compactCogCompiledCode(void);
 void enterCogCodePopReceiver(void);
 void enterCogCodePopReceiverAndClassRegs(void);
-void enterCogCodePopReceiverArg0Regs(void);
-void enterCogCodePopReceiverArg1Arg0Regs(void);
 CogBlockMethod * findEnclosingMethodForinHomeMethod(sqInt mcpc, CogMethod *cogMethod);
 CogBlockMethod * findMethodForStartBcpcinHomeMethod(sqInt startbcpc, CogMethod *cogMethod);
 sqInt genQuickReturnConst(void);
@@ -83,12 +76,7 @@
 sqInt ceCannotResumeTrampoline;
 void (*ceCaptureCStackPointers)(void);
 sqInt ceCheckForInterruptTrampoline;
-void (*ceEnter0ArgsPIC)(void);
-void (*ceEnter1ArgsPIC)(void);
-void (*ceEnter2ArgsPIC)(void);
 void (*ceEnterCogCodePopReceiverAndClassRegs)(void);
-void (*ceEnterCogCodePopReceiverArg0Regs)(void);
-void (*ceEnterCogCodePopReceiverArg1Arg0Regs)(void);
 void (*ceEnterCogCodePopReceiverReg)(void);
 unsigned long (*ceGetSP)(void);
 sqInt ceReturnToInterpreterTrampoline;
@@ -99,8 +87,6 @@
 sqInt cmNoCheckEntryOffset;
 unsigned long debugPrimCallStackOffset;
 void (*realCEEnterCogCodePopReceiverAndClassRegs)(void);
-void (*realCEEnterCogCodePopReceiverArg0Regs)(void);
-void (*realCEEnterCogCodePopReceiverArg1Arg0Regs)(void);
 void (*realCEEnterCogCodePopReceiverReg)(void);
 int traceLinkedSends ;
 sqInt traceStores;
@@ -115,7 +101,7 @@
 #define getCStackPointer() CStackPointer
 #define noCheckEntryOffset() cmNoCheckEntryOffset
 #define noContextSwitchBlockEntryOffset() blockNoContextSwitchOffset
-#define numRegArgs() 1
+#define numRegArgs() 0
 #define printOnTrace() (traceLinkedSends & 8)
 #define recordEventTrace() (traceLinkedSends & 4)
 #define recordPrimTrace() (traceLinkedSends & 2)

Modified: branches/Cog/src/vm/cointerp.c
===================================================================
--- branches/Cog/src/vm/cointerp.c	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/src/vm/cointerp.c	2011-01-01 20:18:49 UTC (rev 2337)
@@ -1,9 +1,9 @@
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CCodeGeneratorGlobalStructure VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
    from
-	CoInterpreter VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99 " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1859,7 +1859,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.40]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.41]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 static volatile int sendTrace;
 
@@ -8649,7 +8649,13 @@
 	GIV(stackPointer) += BytesPerWord;
 	GIV(instructionPointer) = ((sqInt) top);
 	if (primitiveFunctionPointer != 0) {
-		assert((primitiveIndexOf(GIV(newMethod))) != 0);
+		if (primitiveFunctionPointer == (primitiveInvokeObjectAsMethod)) {
+			assert(!(isOopCompiledMethod(GIV(newMethod))));
+		}
+		else {
+			assert((isOopCompiledMethod(GIV(newMethod)))
+			 && ((primitiveIndexOf(GIV(newMethod))) != 0));
+		}
 		(GIV(stackPage)->headFP = GIV(framePointer));
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
@@ -14016,6 +14022,8 @@
     char *sp1;
     char *sp2;
 
+	
+#  if (numRegArgs()) > 0
 	assert(((numRegArgs()) > 0)
 	 && ((numRegArgs()) <= 2));
 	if (((cogMethod->cmNumArgs)) == 2) {
@@ -14046,6 +14054,12 @@
 	longAtput(sp2 = GIV(stackPointer) - BytesPerWord, rcvr);
 	GIV(stackPointer) = sp2;
 	ceEnterCogCodePopReceiverReg();
+
+#  else /* (numRegArgs()) > 0 */
+	assert(0);
+
+#  endif /* (numRegArgs()) > 0 */
+
 }
 
 

Modified: branches/Cog/src/vm/gcc3x-cointerp.c
===================================================================
--- branches/Cog/src/vm/gcc3x-cointerp.c	2010-12-31 19:27:35 UTC (rev 2336)
+++ branches/Cog/src/vm/gcc3x-cointerp.c	2011-01-01 20:18:49 UTC (rev 2337)
@@ -2,11 +2,11 @@
 
 
 /* Automatically generated by
-	CCodeGeneratorGlobalStructure VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CCodeGeneratorGlobalStructure VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
    from
-	CoInterpreter VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99
+	CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c
  */
-static char __buildInfo[] = "CoInterpreter VMMaker-oscog.40 uuid: 637db40c-33c6-4263-816e-1b8cc19e3c99 " __DATE__ ;
+static char __buildInfo[] = "CoInterpreter VMMaker-oscog.41 uuid: 096b8a29-e7e8-4cbf-b29c-0f096abbdd5c " __DATE__ ;
 char *__interpBuildInfo = __buildInfo;
 
 
@@ -1862,7 +1862,7 @@
 	/* 575 */ (void (*)(void))0,
  0 };
 static void (*externalPrimitiveTable[MaxExternalPrimitiveTableSize + 1 /* 4097 */])(void);
-const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.40]";
+const char *interpreterVersion = "Croquet Closure Cog VM [CoInterpreter VMMaker-oscog.41]";
 sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* 10 */;
 static volatile int sendTrace;
 
@@ -1915,12 +1915,13 @@
 interpret(void)
 {   DECL_MAYBE_SQ_GLOBAL_STRUCT
     sqInt backwardJumpCount;
-    sqInt currentBytecode;
+    sqInt currentBytecode CB_REG;
     sqInt lastBackwardJumpMethod;
-    char * localFP;
-    char * localIP;
+    char* localFP FP_REG;
+    char* localIP IP_REG;
     sqInt localReturnValue;
-    char * localSP;
+    char* localSP SP_REG;
+    JUMP_TABLE;
 
 	if (GIV(stackLimit) == 0) {
 		return initStackPagesAndInterpret();
@@ -1938,7 +1939,7 @@
 
 		VM_LABEL(0bytecodeDispatch);
 		switch (currentBytecode) {
-		case 0:
+		CASE(0)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -1950,8 +1951,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((0 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 1:
+			BREAK;
+		CASE(1)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -1963,8 +1964,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((1 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 2:
+			BREAK;
+		CASE(2)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -1976,8 +1977,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((2 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 3:
+			BREAK;
+		CASE(3)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -1989,8 +1990,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((3 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 4:
+			BREAK;
+		CASE(4)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2002,8 +2003,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((4 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 5:
+			BREAK;
+		CASE(5)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2015,8 +2016,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((5 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 6:
+			BREAK;
+		CASE(6)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2028,8 +2029,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((6 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 7:
+			BREAK;
+		CASE(7)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2041,8 +2042,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((7 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 8:
+			BREAK;
+		CASE(8)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2054,8 +2055,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((8 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 9:
+			BREAK;
+		CASE(9)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2067,8 +2068,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((9 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 10:
+			BREAK;
+		CASE(10)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2080,8 +2081,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((10 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 11:
+			BREAK;
+		CASE(11)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2093,8 +2094,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((11 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 12:
+			BREAK;
+		CASE(12)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2106,8 +2107,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((12 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 13:
+			BREAK;
+		CASE(13)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2119,8 +2120,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((13 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 14:
+			BREAK;
+		CASE(14)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2132,8 +2133,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((14 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 15:
+			BREAK;
+		CASE(15)
 			/* pushReceiverVariableBytecode */
 			{
 
@@ -2145,8 +2146,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(((longAt(localFP + FoxIFReceiver)) + BaseHeaderSize) + ((15 & 15) << ShiftForWord)));
 			}
 ;
-			break;
-		case 16:
+			BREAK;
+		CASE(16)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2164,8 +2165,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 17:
+			BREAK;
+		CASE(17)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2183,8 +2184,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 18:
+			BREAK;
+		CASE(18)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2202,8 +2203,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 19:
+			BREAK;
+		CASE(19)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2221,8 +2222,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 20:
+			BREAK;
+		CASE(20)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2240,8 +2241,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 21:
+			BREAK;
+		CASE(21)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2259,8 +2260,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 22:
+			BREAK;
+		CASE(22)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2278,8 +2279,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 23:
+			BREAK;
+		CASE(23)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2297,8 +2298,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 24:
+			BREAK;
+		CASE(24)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2316,8 +2317,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 25:
+			BREAK;
+		CASE(25)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2335,8 +2336,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 26:
+			BREAK;
+		CASE(26)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2354,8 +2355,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 27:
+			BREAK;
+		CASE(27)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2373,8 +2374,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 28:
+			BREAK;
+		CASE(28)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2392,8 +2393,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 29:
+			BREAK;
+		CASE(29)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2411,8 +2412,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 30:
+			BREAK;
+		CASE(30)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2430,8 +2431,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 31:
+			BREAK;
+		CASE(31)
 			/* pushTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -2449,8 +2450,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 32:
+			BREAK;
+		CASE(32)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2466,8 +2467,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 33:
+			BREAK;
+		CASE(33)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2483,8 +2484,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 34:
+			BREAK;
+		CASE(34)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2500,8 +2501,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 35:
+			BREAK;
+		CASE(35)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2517,8 +2518,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 36:
+			BREAK;
+		CASE(36)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2534,8 +2535,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 37:
+			BREAK;
+		CASE(37)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2551,8 +2552,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 38:
+			BREAK;
+		CASE(38)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2568,8 +2569,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 39:
+			BREAK;
+		CASE(39)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2585,8 +2586,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 40:
+			BREAK;
+		CASE(40)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2602,8 +2603,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 41:
+			BREAK;
+		CASE(41)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2619,8 +2620,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 42:
+			BREAK;
+		CASE(42)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2636,8 +2637,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 43:
+			BREAK;
+		CASE(43)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2653,8 +2654,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 44:
+			BREAK;
+		CASE(44)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2670,8 +2671,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 45:
+			BREAK;
+		CASE(45)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2687,8 +2688,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 46:
+			BREAK;
+		CASE(46)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2704,8 +2705,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 47:
+			BREAK;
+		CASE(47)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2721,8 +2722,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 48:
+			BREAK;
+		CASE(48)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2738,8 +2739,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 49:
+			BREAK;
+		CASE(49)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2755,8 +2756,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 50:
+			BREAK;
+		CASE(50)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2772,8 +2773,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 51:
+			BREAK;
+		CASE(51)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2789,8 +2790,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 52:
+			BREAK;
+		CASE(52)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2806,8 +2807,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 53:
+			BREAK;
+		CASE(53)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2823,8 +2824,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 54:
+			BREAK;
+		CASE(54)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2840,8 +2841,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 55:
+			BREAK;
+		CASE(55)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2857,8 +2858,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 56:
+			BREAK;
+		CASE(56)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2874,8 +2875,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 57:
+			BREAK;
+		CASE(57)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2891,8 +2892,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 58:
+			BREAK;
+		CASE(58)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2908,8 +2909,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 59:
+			BREAK;
+		CASE(59)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2925,8 +2926,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 60:
+			BREAK;
+		CASE(60)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2942,8 +2943,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 61:
+			BREAK;
+		CASE(61)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2959,8 +2960,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 62:
+			BREAK;
+		CASE(62)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2976,8 +2977,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 63:
+			BREAK;
+		CASE(63)
 			/* pushLiteralConstantBytecode */
 			{
 				sqInt object;
@@ -2993,8 +2994,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 64:
+			BREAK;
+		CASE(64)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3013,8 +3014,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 65:
+			BREAK;
+		CASE(65)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3033,8 +3034,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 66:
+			BREAK;
+		CASE(66)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3053,8 +3054,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 67:
+			BREAK;
+		CASE(67)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3073,8 +3074,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 68:
+			BREAK;
+		CASE(68)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3093,8 +3094,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 69:
+			BREAK;
+		CASE(69)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3113,8 +3114,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 70:
+			BREAK;
+		CASE(70)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3133,8 +3134,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 71:
+			BREAK;
+		CASE(71)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3153,8 +3154,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 72:
+			BREAK;
+		CASE(72)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3173,8 +3174,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 73:
+			BREAK;
+		CASE(73)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3193,8 +3194,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 74:
+			BREAK;
+		CASE(74)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3213,8 +3214,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 75:
+			BREAK;
+		CASE(75)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3233,8 +3234,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 76:
+			BREAK;
+		CASE(76)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3253,8 +3254,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 77:
+			BREAK;
+		CASE(77)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3273,8 +3274,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 78:
+			BREAK;
+		CASE(78)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3293,8 +3294,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 79:
+			BREAK;
+		CASE(79)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3313,8 +3314,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 80:
+			BREAK;
+		CASE(80)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3333,8 +3334,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 81:
+			BREAK;
+		CASE(81)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3353,8 +3354,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 82:
+			BREAK;
+		CASE(82)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3373,8 +3374,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 83:
+			BREAK;
+		CASE(83)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3393,8 +3394,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 84:
+			BREAK;
+		CASE(84)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3413,8 +3414,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 85:
+			BREAK;
+		CASE(85)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3433,8 +3434,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 86:
+			BREAK;
+		CASE(86)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3453,8 +3454,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 87:
+			BREAK;
+		CASE(87)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3473,8 +3474,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 88:
+			BREAK;
+		CASE(88)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3493,8 +3494,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 89:
+			BREAK;
+		CASE(89)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3513,8 +3514,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 90:
+			BREAK;
+		CASE(90)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3533,8 +3534,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 91:
+			BREAK;
+		CASE(91)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3553,8 +3554,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 92:
+			BREAK;
+		CASE(92)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3573,8 +3574,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 93:
+			BREAK;
+		CASE(93)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3593,8 +3594,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 94:
+			BREAK;
+		CASE(94)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3613,8 +3614,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 95:
+			BREAK;
+		CASE(95)
 			/* pushLiteralVariableBytecode */
 			{
 				sqInt object;
@@ -3633,15 +3634,15 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 96:
-		case 97:
-		case 98:
-		case 99:
-		case 100:
-		case 101:
-		case 102:
-		case 103:
+			BREAK;
+		CASE(96)
+		CASE(97)
+		CASE(98)
+		CASE(99)
+		CASE(100)
+		CASE(101)
+		CASE(102)
+		CASE(103)
 			/* storeAndPopReceiverVariableBytecode */
 			{
 				sqInt rcvr;
@@ -3660,8 +3661,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 104:
+			BREAK;
+		CASE(104)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3681,8 +3682,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 105:
+			BREAK;
+		CASE(105)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3702,8 +3703,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 106:
+			BREAK;
+		CASE(106)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3723,8 +3724,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 107:
+			BREAK;
+		CASE(107)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3744,8 +3745,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 108:
+			BREAK;
+		CASE(108)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3765,8 +3766,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 109:
+			BREAK;
+		CASE(109)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3786,8 +3787,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 110:
+			BREAK;
+		CASE(110)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3807,8 +3808,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 111:
+			BREAK;
+		CASE(111)
 			/* storeAndPopTemporaryVariableBytecode */
 			{
 				sqInt frameNumArgs;
@@ -3828,8 +3829,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 112:
+			BREAK;
+		CASE(112)
 			/* pushReceiverBytecode */
 			{
 
@@ -3840,8 +3841,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt(localFP + FoxIFReceiver));
 			}
 ;
-			break;
-		case 113:
+			BREAK;
+		CASE(113)
 			/* pushConstantTrueBytecode */
 			{
 
@@ -3852,8 +3853,8 @@
 				longAtPointerput(localSP -= BytesPerWord, GIV(trueObj));
 			}
 ;
-			break;
-		case 114:
+			BREAK;
+		CASE(114)
 			/* pushConstantFalseBytecode */
 			{
 
@@ -3864,8 +3865,8 @@
 				longAtPointerput(localSP -= BytesPerWord, GIV(falseObj));
 			}
 ;
-			break;
-		case 115:
+			BREAK;
+		CASE(115)
 			/* pushConstantNilBytecode */
 			{
 
@@ -3876,8 +3877,8 @@
 				longAtPointerput(localSP -= BytesPerWord, GIV(nilObj));
 			}
 ;
-			break;
-		case 116:
+			BREAK;
+		CASE(116)
 			/* pushConstantMinusOneBytecode */
 			{
 
@@ -3888,8 +3889,8 @@
 				longAtPointerput(localSP -= BytesPerWord, ConstMinusOne);
 			}
 ;
-			break;
-		case 117:
+			BREAK;
+		CASE(117)
 			/* pushConstantZeroBytecode */
 			{
 
@@ -3900,8 +3901,8 @@
 				longAtPointerput(localSP -= BytesPerWord, ConstZero);
 			}
 ;
-			break;
-		case 118:
+			BREAK;
+		CASE(118)
 			/* pushConstantOneBytecode */
 			{
 
@@ -3912,8 +3913,8 @@
 				longAtPointerput(localSP -= BytesPerWord, ConstOne);
 			}
 ;
-			break;
-		case 119:
+			BREAK;
+		CASE(119)
 			/* pushConstantTwoBytecode */
 			{
 
@@ -3924,8 +3925,8 @@
 				longAtPointerput(localSP -= BytesPerWord, ConstTwo);
 			}
 ;
-			break;
-		case 120:
+			BREAK;
+		CASE(120)
 			/* returnReceiver */
 			{
 
@@ -4253,8 +4254,8 @@
 			}
 ;
 		l94:	/* end case */;
-			break;
-		case 121:
+			BREAK;
+		CASE(121)
 			/* returnTrue */
 			{
 
@@ -4263,8 +4264,8 @@
 				goto commonReturn;
 			}
 ;
-			break;
-		case 122:
+			BREAK;
+		CASE(122)
 			/* returnFalse */
 			{
 
@@ -4273,8 +4274,8 @@
 				goto commonReturn;
 			}
 ;
-			break;
-		case 123:
+			BREAK;
+		CASE(123)
 			/* returnNil */
 			{
 
@@ -4283,8 +4284,8 @@
 				goto commonReturn;
 			}
 ;
-			break;
-		case 124:
+			BREAK;
+		CASE(124)
 			/* returnTopFromMethod */
 			{
 
@@ -4293,8 +4294,8 @@
 				goto commonReturn;
 			}
 ;
-			break;
-		case 125:
+			BREAK;
+		CASE(125)
 			/* returnTopFromBlock */
 			{
 
@@ -4502,9 +4503,9 @@
 			}
 ;
 		l99:	/* end case */;
-			break;
-		case 126:
-		case 127:
+			BREAK;
+		CASE(126)
+		CASE(127)
 			/* unknownBytecode */
 			{
 
@@ -4512,8 +4513,8 @@
 								error("Unknown bytecode");
 			}
 ;
-			break;
-		case 128:
+			BREAK;
+		CASE(128)
 			/* extendedPushBytecode */
 			{
 				sqInt descriptor;
@@ -4569,8 +4570,8 @@
 			}
 ;
 		l1:	/* end case */;
-			break;
-		case 129:
+			BREAK;
+		CASE(129)
 			/* extendedStoreBytecode */
 			{
 				sqInt association;
@@ -4618,8 +4619,8 @@
 			}
 ;
 		l2:	/* end case */;
-			break;
-		case 130:
+			BREAK;
+		CASE(130)
 			/* extendedStoreAndPopBytecode */
 			{
 				sqInt association;
@@ -4671,8 +4672,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 131:
+			BREAK;
+		CASE(131)
 			/* singleExtendedSendBytecode */
 			{
 				sqInt descriptor;
@@ -5001,8 +5002,8 @@
 				currentBytecode = byteAtPointer(++localIP);
 			}
 ;
-			break;
-		case 132:
+			BREAK;
+		CASE(132)
 			/* doubleExtendedDoAnythingBytecode */
 			{
 				sqInt byte2;
@@ -5340,8 +5341,8 @@
 			}
 ;
 		l4:	/* end case */;
-			break;
-		case 133:
+			BREAK;
+		CASE(133)
 			/* singleExtendedSuperBytecode */
 			{
 				sqInt descriptor;
@@ -5376,8 +5377,8 @@
 				goto commonSend;
 			}
 ;
-			break;
-		case 134:
+			BREAK;
+		CASE(134)
 			/* secondExtendedSendBytecode */
 			{
 				sqInt descriptor;
@@ -5391,8 +5392,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 135:
+			BREAK;
+		CASE(135)
 			/* popStackBytecode */
 			{
 
@@ -5403,8 +5404,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 136:
+			BREAK;
+		CASE(136)
 			/* duplicateTopBytecode */
 			{
 				sqInt object;
@@ -5417,8 +5418,8 @@
 				longAtPointerput(localSP -= BytesPerWord, object);
 			}
 ;
-			break;
-		case 137:
+			BREAK;
+		CASE(137)
 			/* pushActiveContextBytecode */
 			{
 				sqInt ourContext;
@@ -5445,8 +5446,8 @@
 				longAtPointerput(localSP -= BytesPerWord, ourContext);
 			}
 ;
-			break;
-		case 138:
+			BREAK;
+		CASE(138)
 			/* pushNewArrayBytecode */
 			{
 				sqInt array;
@@ -5487,8 +5488,8 @@
 				longAtPointerput(localSP -= BytesPerWord, array);
 			}
 ;
-			break;
-		case 139:
+			BREAK;
+		CASE(139)
 			/* unknownBytecode */
 			{
 
@@ -5496,8 +5497,8 @@
 								error("Unknown bytecode");
 			}
 ;
-			break;
-		case 140:
+			BREAK;
+		CASE(140)
 			/* pushRemoteTempLongBytecode */
 			{
 				sqInt remoteTempIndex;
@@ -5519,8 +5520,8 @@
 				longAtPointerput(localSP -= BytesPerWord, longAt((tempVector + BaseHeaderSize) + (remoteTempIndex << ShiftForWord)));
 			}
 ;
-			break;
-		case 141:
+			BREAK;
+		CASE(141)
 			/* storeRemoteTempLongBytecode */
 			{
 				sqInt remoteTempIndex;
@@ -5545,8 +5546,8 @@
 				longAtput((tempVector + BaseHeaderSize) + (remoteTempIndex << ShiftForWord), longAtPointer(localSP));
 			}
 ;
-			break;
-		case 142:
+			BREAK;
+		CASE(142)
 			/* storeAndPopRemoteTempLongBytecode */
 			{
 				sqInt remoteTempIndex;
@@ -5574,8 +5575,8 @@
 				localSP += 1 * BytesPerWord;
 			}
 ;
-			break;
-		case 143:
+			BREAK;
+		CASE(143)
 			/* pushClosureCopyCopiedValuesBytecode */
 			{
 				sqInt blockSize;
@@ -5645,8 +5646,8 @@
 				longAtPointerput(localSP -= BytesPerWord, newClosure);
 			}
 ;
-			break;
-		case 144:
+			BREAK;
+		CASE(144)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5658,8 +5659,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 145:
+			BREAK;
+		CASE(145)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5671,8 +5672,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 146:
+			BREAK;
+		CASE(146)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5684,8 +5685,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 147:
+			BREAK;
+		CASE(147)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5697,8 +5698,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 148:
+			BREAK;
+		CASE(148)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5710,8 +5711,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 149:
+			BREAK;
+		CASE(149)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5723,8 +5724,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 150:
+			BREAK;
+		CASE(150)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5736,8 +5737,8 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 151:
+			BREAK;
+		CASE(151)
 			/* shortUnconditionalJump */
 			{
 				sqInt offset;
@@ -5749,15 +5750,15 @@
 				currentBytecode = byteAtPointer(localIP);
 			}
 ;
-			break;
-		case 152:
-		case 153:
-		case 154:
-		case 155:
-		case 156:
-		case 157:
-		case 158:
-		case 159:
+			BREAK;
+		CASE(152)
+		CASE(153)
+		CASE(154)
+		CASE(155)
+		CASE(156)
+		CASE(157)
+		CASE(158)
+		CASE(159)
 			/* shortConditionalJump */
 			{
 				sqInt offset;
@@ -5788,15 +5789,15 @@
 			l10:	/* end jumplfFalseBy: */;
 			}
 ;
-			break;
-		case 160:
-		case 161:
-		case 162:
-		case 163:
-		case 164:
-		case 165:
-		case 166:
-		case 167:
+			BREAK;
+		CASE(160)
+		CASE(161)
+		CASE(162)
+		CASE(163)
+		CASE(164)
+		CASE(165)
+		CASE(166)
+		CASE(167)
 			/* longUnconditionalJump */
 			{
 				sqInt offset;
@@ -5940,11 +5941,11 @@
 				currentBytecode = byteAtPointer(++localIP);
 			}
 ;
-			break;
-		case 168:
-		case 169:
-		case 170:
-		case 171:
+			BREAK;
+		CASE(168)
+		CASE(169)
+		CASE(170)
+		CASE(171)
 			/* longJumpIfTrue */
 			{
 				sqInt offset;
@@ -5975,11 +5976,11 @@
 			l11:	/* end jumplfTrueBy: */;
 			}
 ;
-			break;
-		case 172:
-		case 173:
-		case 174:
-		case 175:
+			BREAK;
+		CASE(172)
+		CASE(173)
+		CASE(174)
+		CASE(175)
 			/* longJumpIfFalse */
 			{
 				sqInt offset;
@@ -6010,8 +6011,8 @@
 			l12:	/* end jumplfFalseBy: */;
 			}
 ;
-			break;
-		case 176:
+			BREAK;
+		CASE(176)
 			/* bytecodePrimAdd */
 			{
 				sqInt arg;
@@ -6141,8 +6142,8 @@
 			}
 ;
 		l13:	/* end case */;
-			break;
-		case 177:
+			BREAK;
+		CASE(177)
 			/* bytecodePrimSubtract */
 			{
 				sqInt arg;
@@ -6272,8 +6273,8 @@
 			}
 ;
 		l18:	/* end case */;
-			break;
-		case 178:
+			BREAK;
+		CASE(178)
 			/* bytecodePrimLessThan */
 			{
 				sqInt aBool;
@@ -6424,8 +6425,8 @@
 			}
 ;
 		l107:	/* end case */;
-			break;
-		case 179:
+			BREAK;
+		CASE(179)
 			/* bytecodePrimGreaterThan */
 			{
 				sqInt aBool;
@@ -6582,8 +6583,8 @@
 			}
 ;
 		l108:	/* end case */;
-			break;
-		case 180:
+			BREAK;
+		CASE(180)
 			/* bytecodePrimLessOrEqual */
 			{
 				sqInt aBool;
@@ -6701,8 +6702,8 @@
 			}
 ;
 		l33:	/* end case */;
-			break;
-		case 181:
+			BREAK;
+		CASE(181)
 			/* bytecodePrimGreaterOrEqual */
 			{
 				sqInt aBool;
@@ -6820,8 +6821,8 @@
 			}
 ;
 		l38:	/* end case */;
-			break;
-		case 182:
+			BREAK;
+		CASE(182)
 			/* bytecodePrimEqual */
 			{
 				sqInt aBool;
@@ -6939,8 +6940,8 @@
 			}
 ;
 		l43:	/* end case */;
-			break;
-		case 183:
+			BREAK;
+		CASE(183)
 			/* bytecodePrimNotEqual */
 			{
 				sqInt aBool;
@@ -7058,8 +7059,8 @@
 			}
 ;
 		l48:	/* end case */;
-			break;
-		case 184:
+			BREAK;
+		CASE(184)
 			/* bytecodePrimMultiply */
 			{
 				sqInt arg;
@@ -7193,8 +7194,8 @@
 			}
 ;
 		l53:	/* end case */;
-			break;
-		case 185:
+			BREAK;
+		CASE(185)
 			/* bytecodePrimDivide */
 			{
 				sqInt arg;
@@ -7341,8 +7342,8 @@
 			}
 ;
 		l58:	/* end case */;
-			break;
-		case 186:
+			BREAK;
+		CASE(186)
 			/* bytecodePrimMod */
 			{
 				sqInt mod;
@@ -7364,8 +7365,8 @@
 			}
 ;
 		l63:	/* end case */;
-			break;
-		case 187:
+			BREAK;
+		CASE(187)
 			/* bytecodePrimMakePoint */
 			{
 				sqInt argument;
@@ -7461,8 +7462,8 @@
 			}
 ;
 		l64:	/* end case */;
-			break;
-		case 188:
+			BREAK;
+		CASE(188)
 			/* bytecodePrimBitShift */
 			{
 				sqInt integerArgument;
@@ -7571,8 +7572,8 @@
 			}
 ;
 		l66:	/* end case */;
-			break;
-		case 189:
+			BREAK;
+		CASE(189)
 			/* bytecodePrimDiv */
 			{
 				sqInt quotient;
@@ -7594,8 +7595,8 @@
 			}
 ;
 		l68:	/* end case */;
-			break;
-		case 190:
+			BREAK;
+		CASE(190)
 			/* bytecodePrimBitAnd */
 			{
 				sqInt integerArgument;
@@ -7654,8 +7655,8 @@
 			}
 ;
 		l69:	/* end case */;
-			break;
-		case 191:
+			BREAK;
+		CASE(191)
 			/* bytecodePrimBitOr */
 			{
 				sqInt integerArgument;
@@ -7714,8 +7715,8 @@
 			}
 ;
 		l70:	/* end case */;
-			break;
-		case 192:
+			BREAK;
+		CASE(192)
 			/* bytecodePrimAt */
 			{
 				sqInt atIx;
@@ -7812,8 +7813,8 @@
 			}
 ;
 		l71:	/* end case */;
-			break;
-		case 193:
+			BREAK;
+		CASE(193)
 			/* bytecodePrimAtPut */
 			{
 				sqInt atIx;
@@ -7934,8 +7935,8 @@
 			}
 ;
 		l74:	/* end case */;
-			break;
-		case 194:
+			BREAK;
+		CASE(194)
 			/* bytecodePrimSize */
 			{
 				sqInt isArray;
@@ -8047,8 +8048,8 @@
 			}
 ;
 		l77:	/* end case */;
-			break;
-		case 195:
+			BREAK;
+		CASE(195)
 			/* bytecodePrimNext */
 			{
 
@@ -8058,8 +8059,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 196:
+			BREAK;
+		CASE(196)
 			/* bytecodePrimNextPut */
 			{
 
@@ -8069,8 +8070,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 197:
+			BREAK;
+		CASE(197)
 			/* bytecodePrimAtEnd */
 			{
 
@@ -8080,8 +8081,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 198:
+			BREAK;
+		CASE(198)
 			/* bytecodePrimEquivalent */
 			{
 				sqInt arg;
@@ -8099,8 +8100,8 @@
 				}
 			}
 ;
-			break;
-		case 199:
+			BREAK;
+		CASE(199)
 			/* bytecodePrimClass */
 			{
 				sqInt rcvr;
@@ -8129,8 +8130,8 @@
 				currentBytecode = byteAtPointer(++localIP);
 			}
 ;
-			break;
-		case 200:
+			BREAK;
+		CASE(200)
 			/* bytecodePrimBlockCopy */
 			{
 
@@ -8140,8 +8141,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 201:
+			BREAK;
+		CASE(201)
 			/* bytecodePrimValue */
 			{
 				sqInt isBlock;
@@ -8190,8 +8191,8 @@
 			}
 ;
 		l83:	/* end case */;
-			break;
-		case 202:
+			BREAK;
+		CASE(202)
 			/* bytecodePrimValueWithArg */
 			{
 				sqInt isBlock;
@@ -8240,8 +8241,8 @@
 			}
 ;
 		l85:	/* end case */;
-			break;
-		case 203:
+			BREAK;
+		CASE(203)
 			/* bytecodePrimDo */
 			{
 
@@ -8251,8 +8252,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 204:
+			BREAK;
+		CASE(204)
 			/* bytecodePrimNew */
 			{
 
@@ -8262,8 +8263,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 205:
+			BREAK;
+		CASE(205)
 			/* bytecodePrimNewWithArg */
 			{
 
@@ -8273,8 +8274,8 @@
 				goto normalSend;
 			}
 ;
-			break;
-		case 206:
+			BREAK;
+		CASE(206)
 			/* bytecodePrimPointX */
 			{
 				sqInt rcvr;
@@ -8319,8 +8320,8 @@
 			}
 ;
 		l87:	/* end case */;
-			break;
-		case 207:
+			BREAK;
+		CASE(207)
 			/* bytecodePrimPointY */
 			{
 				sqInt rcvr;
@@ -8365,23 +8366,23 @@
 			}
 ;
 		l89:	/* end case */;
-			break;
-		case 208:
-		case 209:
-		case 210:
-		case 211:
-		case 212:
-		case 213:
-		case 214:
-		case 215:
-		case 216:
-		case 217:
-		case 218:
-		case 219:
-		case 220:
-		case 221:
-		case 222:
-		case 223:
+			BREAK;
+		CASE(208)
+		CASE(209)
+		CASE(210)
+		CASE(211)
+		CASE(212)
+		CASE(213)
+		CASE(214)
+		CASE(215)
+		CASE(216)
+		CASE(217)
+		CASE(218)
+		CASE(219)
+		CASE(220)
+		CASE(221)
+		CASE(222)
+		CASE(223)
 			/* sendLiteralSelector0ArgsBytecode */
 			{
 				sqInt rcvr;
@@ -8411,23 +8412,23 @@
 				goto commonSend;
 			}
 ;
-			break;
-		case 224:
-		case 225:
-		case 226:
-		case 227:
-		case 228:
-		case 229:
-		case 230:
-		case 231:
-		case 232:
-		case 233:
-		case 234:
-		case 235:
-		case 236:
-		case 237:
-		case 238:
-		case 239:
+			BREAK;
+		CASE(224)
+		CASE(225)
+		CASE(226)
+		CASE(227)
+		CASE(228)
+		CASE(229)
+		CASE(230)
+		CASE(231)
+		CASE(232)
+		CASE(233)
+		CASE(234)
+		CASE(235)
+		CASE(236)
+		CASE(237)
+		CASE(238)
+		CASE(239)
 			/* sendLiteralSelector1ArgBytecode */
 			{
 				sqInt rcvr;
@@ -8457,23 +8458,23 @@
 				goto commonSend;
 			}
 ;
-			break;
-		case 240:
-		case 241:
-		case 242:
-		case 243:
-		case 244:
-		case 245:
-		case 246:
-		case 247:
-		case 248:
-		case 249:
-		case 250:
-		case 251:
-		case 252:
-		case 253:
-		case 254:
-		case 255:
+			BREAK;
+		CASE(240)
+		CASE(241)
+		CASE(242)
+		CASE(243)
+		CASE(244)
+		CASE(245)
+		CASE(246)
+		CASE(247)
+		CASE(248)
+		CASE(249)
+		CASE(250)
+		CASE(251)
+		CASE(252)
+		CASE(253)
+		CASE(254)
+		CASE(255)
 			/* sendLiteralSelector2ArgsBytecode */
 			{
 				sqInt rcvr;
@@ -8503,7 +8504,7 @@
 				goto commonSend;
 			}
 ;
-			break;
+			BREAK;
 		}
 	}
 
@@ -8652,7 +8653,13 @@
 	GIV(stackPointer) += BytesPerWord;
 	GIV(instructionPointer) = ((sqInt) top);
 	if (primitiveFunctionPointer != 0) {
-		assert((primitiveIndexOf(GIV(newMethod))) != 0);
+		if (primitiveFunctionPointer == (primitiveInvokeObjectAsMethod)) {
+			assert(!(isOopCompiledMethod(GIV(newMethod))));
+		}
+		else {
+			assert((isOopCompiledMethod(GIV(newMethod)))
+			 && ((primitiveIndexOf(GIV(newMethod))) != 0));
+		}
 		(GIV(stackPage)->headFP = GIV(framePointer));
 		if ((((unsigned long) primitiveFunctionPointer)) <= MaxQuickPrimitiveIndex) {
 			externalQuickPrimitiveResponse();
@@ -14019,6 +14026,8 @@
     char *sp1;
     char *sp2;
 
+	
+#  if (numRegArgs()) > 0
 	assert(((numRegArgs()) > 0)
 	 && ((numRegArgs()) <= 2));
 	if (((cogMethod->cmNumArgs)) == 2) {
@@ -14049,6 +14058,12 @@
 	longAtput(sp2 = GIV(stackPointer) - BytesPerWord, rcvr);
 	GIV(stackPointer) = sp2;
 	ceEnterCogCodePopReceiverReg();
+
+#  else /* (numRegArgs()) > 0 */
+	assert(0);
+
+#  endif /* (numRegArgs()) > 0 */
+
 }
 
 



More information about the Vm-dev mailing list