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

commits at source.squeak.org commits at source.squeak.org
Fri Nov 30 23:02:41 UTC 2012


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

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

Name: VMMaker.oscog-eem.225
Author: eem
Time: 30 November 2012, 3:00:22.493 pm
UUID: 222bea80-06c8-4893-b1e1-d191688f36e6
Ancestors: VMMaker.oscog-lw.224

Fixes for cog issue 109, base frames and CallPrimitive, and merge
with VMMaker.oscog-lw.224.

Cogit:
StackToRegisterMappingCogit, cog issue 109.
Fix pc mapping for popped folded constants as in, e.g. 1-1.  Need to
check for annotateUse on popping a stack descriptor.

Fix a typo in generateNewspeakRuntime.

CoInterpreter:
Fix makeBaseFrame: for methods with CallPrimitive that get restarted.
e.g. on:do:.  We could make the CallPrimitive bytecode check for
being at the start of a method, but I have decided, for strictness, to
make executing CallPrimitive an error for the moment.  This means
that thater we could use it to embed primitive calls in the middle of methods.

Refactor inverse pc mapping check and make StackInterpreter's
and CoInterpreters makeBaseFrame: closer.

Streamline once again activation sequence to make setting method
(actually bytecodeSetSelector) faster and on primitive failure to
increment pc past CallPrimitive before checking for err code store.

Make ensureMethodIsCogged: answer the cogged method, again for
efficiency.

Add tracing of stack overflows.

Fix bug in printing of bytecode addresses in long/printOop: on
CompiledMethods.

Fix bug in printStringOf: so that it prints ... when truncating.

Add missing case to isNullExternalPrimitiveCall:.

Streamline long/printReferencesTo:.

Simulator:
Make startInContextSuchThat: return on error, allowing one to
proceed past a failure to find a suitable context on startup.

Slang:
Fix bug in super expansion to avoid renaming arguments.  Only
locals should be renamed to avoid conflicts.  Arguments are shared.

Improve formatting of code for cppIf:ifTrue:.

=============== Diff against VMMaker.oscog-lw.224 ===============

Item was changed:
  ----- Method: CCodeGenerator>>generateInlineCppIfElse:asArgument:on:indent: (in category 'C translation') -----
  generateInlineCppIfElse: msgNode asArgument: asArgument on: aStream indent: level
  	"Generate the C code for this message onto the given stream."
  	| expr putStatement |
  	"Compile-time expansion for constants set in the options dictionary,
  	 e.g. to cut down on noise for MULTIPLEBYTECODESETS."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting if it takes multiple lines, so post-process."
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeAsArgumentOn: s level: level generator: self].
  			  aStream nextPutAll:
+ 			  ((expansion includes: Character cr)
+ 				ifTrue:
+ 					[(String streamContents:
+ 							[:s|
+ 							s position > 0 ifTrue: [s tab: level + 1].
+ 							node emitCCodeAsArgumentOn: s level: level generator: self])
+ 						copyReplaceAll: (String with: Character cr)
+ 						with: (String with: Character cr), (String new: level + 1 withAll: Character tab)]
+ 				ifFalse: [expansion])]]
- 				((expansion includes: Character cr)
- 					ifTrue:
- 						[(String streamContents:
- 								[:s|
- 								s next: level + 1 put: Character tab.
- 								node emitCCodeAsArgumentOn: s level: level generator: self])
- 							copyReplaceAll: (String with: Character cr)
- 							with: (String with: Character cr), (String new: level + 1 withAll: Character tab)]
- 					ifFalse: [expansion])]]
  		ifFalse:
  			[[:node| | expansion |
  			  expansion := String streamContents: [:s| node emitCCodeOn: s level: level generator: self].
  			 "Remove tabs from first line to avoid indenting a second time"
+ 			 expansion := expansion allButFirst: (expansion findFirst: [:c| c ~~ Character tab]) - 1.
- 			 (aStream position > 0 and: [aStream last ~= Character tab]) ifTrue:
- 				[expansion := expansion allButFirst: (expansion findFirst: [:c| c ~~ Character tab]) - 1].
  			 aStream nextPutAll: expansion]].
  
  	(optionsDictionary notNil
  	 and: [msgNode args first isConstant
  	 and: [#(true false) includes: (optionsDictionary at: msgNode args first name ifAbsent: [nil])]]) ifTrue:
  		[(optionsDictionary at: msgNode args first name)
  			ifTrue:
  				[putStatement value: msgNode args second]
  			ifFalse:
  				[msgNode args size >= 3 ifTrue:
  					[putStatement value: msgNode args third]].
  		 ^self].
  
  	"Full #if ... #else..."
  	putStatement := asArgument
  		ifTrue: "emitCCodeAsArgumentOn: doesn't indent, the code needs indenting in this case, so post-process."
  			[[:node|
  			  aStream nextPutAll:
  				((String streamContents:
  						[:s|
  						s next: level + 1 put: Character tab.
  						node emitCCodeAsArgumentOn: s level: level generator: self])
  					copyReplaceAll: (String with: Character cr)
  					with: (String with: Character cr), (String new: level + 1 withAll: Character tab))]]
  		ifFalse:
  			[[:node| node emitCCodeOn: aStream level: level generator: self]].
  
  	expr := String streamContents:
  				[:es|
  				msgNode args first
  					emitCCodeAsArgumentOn: es
  					level: 0
  					generator: self].
  	[expr last isSeparator] whileTrue:
  		[expr := expr allButLast].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'if '; nextPutAll: expr; cr.
  
  	self with: msgNode args first
  		ifAppropriateSetTo: true
  		do: [putStatement value: msgNode args second].
  	expr := ' /* ', expr, ' */'.
  	msgNode args size >= 3 ifTrue:
  		[aStream
  			ensureCr;
  			nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'else'; nextPutAll: expr;
  			cr.
  		self with: msgNode args first
  			ifAppropriateSetTo: false
  			do: [putStatement value: msgNode args third]].
  	aStream
  		ensureCr;
  		nextPut: $#; next: level * 2 put: Character space; nextPutAll: 'endif'; nextPutAll: expr;
  		cr.
  	asArgument ifTrue:
  		[aStream next: level + 1 put: Character tab]!

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
  	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod lastBackwardJumpMethod backwardJumpCount reenterInterpreter deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod processHasThreadId flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile noThreadingOfGUIThread'
+ 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield CogitClass HasBeenReturnedFromMCPC MinBackwardJumpCountForCompile PrimTraceLogSize ReturnToInterpreter RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
- 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield CogitClass HasBeenReturnedFromMCPC MinBackwardJumpCountForCompile PrimTraceLogSize ReturnToInterpreter RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TraceSources TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: '<historical>' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.!

Item was changed:
  ----- Method: CoInterpreter class>>initializeMiscConstantsWith: (in category 'initialization') -----
  initializeMiscConstantsWith: optionsDictionary
  
  	super initializeMiscConstantsWith: optionsDictionary.
  	COGVM := true.
  
  	MinBackwardJumpCountForCompile := 10.
  
  	MaxNumArgs := 15.
  	PrimCallNeedsNewMethod := 1.
  	PrimCallNeedsPrimitiveFunction := 2.
  	PrimCallMayCallBack := 4.
  	PrimCallCollectsProfileSamples := 8.
  
  	ReturnToInterpreter := 1. "setjmp/longjmp code."
  
  	GCModeFull := 1.
  	GCModeIncr := 2.
  	GCModeBecome := 3.
  
  	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
  	TraceBufferSize := 256 * 3. "Room for 256 events"
  	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
  	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
  	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
  	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
  	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
  	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
  	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
  	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
  	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
  	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
  	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
  	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
+ 	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
  
  	TraceIsFromMachineCode := 1.
  	TraceIsFromInterpreter := 2.
  	CSCallbackEnter := 3.
  	CSCallbackLeave := 4.
  	CSEnterCriticalSection := 5.
  	CSExitCriticalSection := 6.
  	CSResume := 7.
  	CSSignal := 8.
  	CSSuspend := 9.
  	CSWait := 10.
  	CSYield := 11.
  	CSCheckEvents := 12.
  	CSThreadSchedulingLoop := 13.
  	CSOwnVM := 14.
  	CSThreadBind := 15.
  	CSSwitchIfNeccessary := 16.
  
  	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
  
  	"this is simulation only"
  	RumpCStackSize := 4096!

Item was changed:
  ----- Method: CoInterpreter>>activateCoggedNewMethod: (in category 'message sending') -----
  activateCoggedNewMethod: inInterpreter
  	"Activate newMethod when newMethod has been cogged, i.e. create a machine-code frame and (re)enter machine-code."
  	| methodHeader cogMethod rcvr numTemps errorCode switched |
  	<var: #cogMethod type: #'CogMethod *'>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader).
  
  	cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  	methodHeader := cogMethod methodHeader.
  	rcvr := self stackValue: cogMethod cmNumArgs. "could new rcvr be set at point of send?"
  	self push: instructionPointer.
  	cogMethod stackCheckOffset = 0 ifTrue:
  		["frameless method; nothing to activate..."
  		 self
  			cppIf: cogit numRegArgs > 0
  		  	ifTrue:
  				[cogMethod cmNumArgs <= cogit numRegArgs ifTrue:
  					[self enterRegisterArgCogMethod: cogMethod at: cogit noCheckEntryOffset receiver: rcvr]].
  		 self push: cogMethod asInteger + cogit noCheckEntryOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: cogMethod asInteger.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	cogMethod cmNumArgs + 1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		[| initialPC |
+ 		 "Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
+ 		 initialPC := (self initialPCForHeader: methodHeader method: newMethod) + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: initialPC) = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		"Store the error code if the method starts with a long store temp.  No instructionPointer skip because we're heading for machine code."
- 		initialPC := self initialPCForHeader: methodHeader method: newMethod.
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: (self pointerForOop: initialPC)) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0]].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	stackPointer >= stackLimit ifTrue:
  		[self assert: cogMethod stackCheckOffset > cogit noCheckEntryOffset.
  		 self push: cogMethod asInteger + cogMethod stackCheckOffset.
  		 self push: rcvr.
  		 cogit ceEnterCogCodePopReceiverReg.
  		 self error: 'should not be reached'].
  	instructionPointer := cogMethod asInteger + cogMethod stackCheckOffset.
  	switched := self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>activateNewClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod.
  	 Override to handle the various interpreter/machine code transitions
  	 and to create an appropriate frame layout."
  	| numCopied outerContext theMethod methodHeader inInterpreter closureIP switched |
  	<inline: true>
  	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	self assert: outerContext ~= blockClosure.
  	numCopied := self copiedValueCountOfClosure: blockClosure.
  	theMethod := objectMemory fetchPointer: MethodIndex ofObject: outerContext.
  	methodHeader := self rawHeaderOf: theMethod.
  	(self isCogMethodReference: methodHeader) ifTrue:
  		[^self executeCogBlock: (self cogMethodOf: theMethod)
  			closure: blockClosure
  			mayContextSwitch: mayContextSwitch].
  	"How do we know when to compile a block method?
  	 One simple criterion is to check if the block is running within its inner context,
  	 i.e. if the outerContext is married.
  	 Even simpler is to remember the previous block entered via the interpreter and
  	 compile if this is the same one.  But we can thrash trying to compile an uncoggable
  	 method unless we try and remember which ones can't be cogged.  So also record
  	 the last block method we failed to compile and avoid recompiling it."
  	(self methodWithHeaderShouldBeCogged: methodHeader)
  		ifTrue:
  			[theMethod = lastCoggableInterpretedBlockMethod
  				ifTrue:
  					[theMethod ~= lastUncoggableInterpretedBlockMethod ifTrue:
  						[cogit cog: theMethod selector: objectMemory nilObject.
  						 (self methodHasCogMethod: theMethod) ifTrue:
  							[^self executeCogBlock: (self cogMethodOf: theMethod)
  								closure: blockClosure
  								mayContextSwitch: mayContextSwitch].
  						 cogCompiledCodeCompactionCalledFor ifFalse:
  							[lastUncoggableInterpretedBlockMethod := theMethod]]]
  				ifFalse:
  					[lastCoggableInterpretedBlockMethod := theMethod]]
  		ifFalse:
  			[self maybeFlagMethodAsInterpreted: theMethod].
  
  	self assert: (self methodHasCogMethod: theMethod) not.
  	"Because this is an uncogged method we need to continue via the interpreter.
  	 We could have been reached either from the interpreter, in which case we
  	 should simply return, or from a machine code frame or from a compiled
  	 primitive.  In these latter two cases we must longjmp back to the interpreter.
  	 The instructionPointer tells us which path we took.
  	 If the sender was an interpreter frame but called through a (failing) primitive
  	 then make sure we restore the saved instruction pointer and avoid pushing
  	 ceReturnToInterpreterPC which is only valid between an interpreter caller
  	 frame and a machine code callee frame."
  	(inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
  		[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  			[instructionPointer := self iframeSavedIP: framePointer]].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
  	self push: (objectMemory fetchPointer: ReceiverIndex ofObject: outerContext).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + ClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	"The initial instructions in the block nil-out remaining temps."
  
  	"the instruction pointer is a pointer variable equal to 
  	method oop + ip + BaseHeaderSize 
  	-1 for 0-based addressing of fetchByte 
  	-1 because it gets incremented BEFORE fetching currentByte"
  	closureIP := self quickFetchInteger: ClosureStartPCIndex ofObject: blockClosure.
  	instructionPointer := theMethod + closureIP + BaseHeaderSize - 2.
+ 	self setMethod: theMethod methodHeader: methodHeader.
- 	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	switched := false.
  	stackPointer < stackLimit ifTrue:
  		[switched := self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch].
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode inInterpreter switched |
  
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  
  	"Because this is an uncogged method we need to continue via the interpreter.
  	 We could have been reached either from the interpreter, in which case we
  	 should simply return, or from a machine code frame or from a compiled
  	 primitive.  In these latter two cases we must longjmp back to the interpreter.
  	 The instructionPointer tells us which path we took.
  	 If the sender was an interpreter frame but called through a (failing) primitive
  	 then make sure we restore the saved instruction pointer and avoid pushing
  	 ceReturnToInterpreterPC which is only valid between an interpreter caller
  	 frame and a machine code callee frame."
  	(inInterpreter := instructionPointer >= objectMemory startOfMemory) ifFalse:
  		[instructionPointer = cogit ceReturnToInterpreterPC ifTrue:
  			[instructionPointer := self iframeSavedIP: framePointer]].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: newMethod.
+ 	self setMethod: newMethod methodHeader: methodHeader.
- 	self setMethod: newMethod.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: instructionPointer + 1)
+ 			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method
- 		  starts with a long store temp.  Strictly no need to skip the store because it's a noop."
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: instructionPointer + 1) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0].
- 		instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)].
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	switched := true.
  	stackPointer < stackLimit ifTrue:
  		[switched := self handleStackOverflowOrEventAllowContextSwitch:
  							(self canContextSwitchIfActivating: newMethod header: methodHeader)].
  	self returnToExecutive: inInterpreter postContextSwitch: switched!

Item was changed:
  ----- Method: CoInterpreter>>ensureMethodIsCogged: (in category 'frame access') -----
  ensureMethodIsCogged: methodObj
+ 	<returnTypeC: #'CogMethod *'>
+ 	| rawHeader cogMethod |
+ 	<inline: true>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 	rawHeader := self rawHeaderOf: methodObj.
+ 	(self isCogMethodReference: rawHeader) ifTrue:
+ 		[^self cCoerceSimple: rawHeader to: #'CogMethod *'].
+ 	cogMethod := cogit cog: methodObj selector: objectMemory nilObject.
+ 	(cogMethod = nil
+ 	 and: [cogCompiledCodeCompactionCalledFor]) ifTrue:
+ 		[self commenceCogCompiledCodeCompaction.
+ 		 cogMethod := cogit cog: methodObj selector: objectMemory nilObject].
+ 	(self asserta: cogMethod ~= nil) ifFalse:
+ 		[self error: 'could not compile method that should have been compiled'].
+ 	^cogMethod!
- 	(self methodHasCogMethod: methodObj) ifFalse:
- 		[((cogit cog: methodObj selector: objectMemory nilObject) = nil
- 		   and: [cogCompiledCodeCompactionCalledFor]) ifTrue:
- 			[self commenceCogCompiledCodeCompaction.
- 			 cogit cog: methodObj selector: objectMemory nilObject]].
- 	(self asserta: (self methodHasCogMethod: methodObj)) ifFalse:
- 		[self error: 'could not compile method that should have been compiled']!

Item was removed:
- ----- Method: CoInterpreter>>iframeInstructionPointerForIndex:method: (in category 'frame access') -----
- iframeInstructionPointerForIndex: ip method: aMethod
- 	"Answer the instruction pointer for use in an interpreter frame (a pointer to a bytecode)."
- 	self assert: (ip between: (objectMemory lastPointerOf: aMethod) and: (objectMemory lengthOf: aMethod)).
- 	^aMethod + ip + BaseHeaderSize - 2!

Item was changed:
  ----- Method: CoInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode switched |
  	<inline: true>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader) not.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
+ 	self setMethod: newMethod methodHeader: methodHeader.
- 	self setMethod: newMethod.
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: 0. "FoxIFSavedIP"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: localIP + 1)
+ 			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method
- 		  starts with a long store temp.  Strictly no need to skip the store because it's a noop."
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: localIP + 1) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0].
- 		localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader)].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 switched := self handleStackOverflowOrEventAllowContextSwitch:
  						(self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self returnToExecutive: true postContextSwitch: switched.
  		 self internalizeIPandSP]!

Item was added:
+ ----- Method: CoInterpreter>>isMachineCodeIP: (in category 'debug support') -----
+ isMachineCodeIP: anInstrPointer
+ 	^anInstrPointer < objectMemory startOfMemory!

Item was changed:
  ----- Method: CoInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
  	| methodHeader activateCogMethod cogMethod numArgs numTemps rcvr errorCode initialIP |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #initialIP type: #usqInt>
  	<inline: true>
  	methodHeader := self rawHeaderOf: newMethod.
  	(activateCogMethod := self isCogMethodReference: methodHeader) ifTrue:
  		[cogMethod := self cCoerceSimple: methodHeader to: #'CogMethod *'.
  		 methodHeader := cogMethod methodHeader].
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  
  	(activateCogMethod
  	and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	initialIP := self initialPCForHeader: methodHeader method: newMethod.
  	activateCogMethod
  		ifTrue:
  			[self push: cogMethod asUnsignedInteger.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 instructionPointer := cogMethod asUnsignedInteger + cogMethod stackCheckOffset]
  		ifFalse:
  			[self push: newMethod.
+ 			 self setMethod: newMethod methodHeader: methodHeader.
- 			 self setMethod: newMethod.
  			 self push: objectMemory nilObject. "FoxThisContext field"
  			 self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  			 self push: 0. "FoxIFSavedIP"
  			 instructionPointer := initialIP - 1].
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 initialIP := initialIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		activateCogMethod ifFalse:
+ 			[instructionPointer := initialIP].
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: initialIP + 1)
+ 			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method
- 		  starts with a long store temp.  Strictly no need to skip the store because it's a noop."
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: initialIP) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0].
- 		activateCogMethod ifFalse:
- 			[instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)]].
  
  	^methodHeader!

Item was changed:
  ----- Method: CoInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
  	"Marry aContext with the base frame of a new stack page.  Build the base
  	 frame to reflect the context's state.  Answer the new page.  Override to
  	 hold the caller context in a different place,  In the StackInterpreter we use
  	 the caller saved ip, but in the Cog VM caller saved ip is the ceBaseReturn:
  	 trampoline.  Simply hold the caller context in the first word of the stack."
+ 	<returnTypeC: #'StackPage *'>
  	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
- 	<returnTypeC: #'StackPage *'>
  	self assert: (self isSingleContext: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC signedIntFromLong < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory fetchPointer: MethodIndex ofObject: aContext.
  	page := self newStackPage.
  	"first word on stack is caller context of base frame"
  	stackPages
  		longAt: (pointer := page baseAddress)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"second word is the context itself; needed for cannotReturn processing; see ceBaseReturn:."
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: aContext.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
+ 	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
- 	maybeClosure := (objectMemory fetchPointer: ClosureIndex ofObject: aContext).
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: maybeClosure]
  		ifFalse:
+ 			[| header |
+ 			 header := self headerOf: theMethod.
+ 			 numArgs := self argumentCountOfMethodHeader: header.
+ 			 self cppIf: MULTIPLEBYTECODESETS
+ 				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
+ 					[(theIP signedIntFromLong > 0
+ 					  and: [(self methodHeaderHasPrimitive: header)
+ 					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) ifTrue:
+ 						[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)]].
- 			[numArgs := self argumentCountOf: theMethod.
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: (objectMemory fetchPointer: ReceiverIndex ofObject: aContext)].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is base return trampoline"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: cogit ceBaseFrameReturnPC.
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: 0.
  	"N.B.  Don't set the baseFP, which marks the page as in use, until after
  	 ensureMethodIsCogged: and/or instructionPointer:forContext:frame:. These
  	 can cause a compiled code compaction which, if marked as in use, will
  	 examine this partially initialized page and crash."
  	page headFP: pointer.
  	"Create either a machine code frame or an interpreter frame based on the pc.  If the pc is -ve
  	 it is a machine code pc and so we produce a machine code frame.  If +ve an interpreter frame.
  	 N.B. Do *not* change this to try and map from a bytecode pc to a machine code frame under
  	 any circumstances.  See ensureContextIsExecutionSafeAfterAssignToStackPointer:"
  	theIP signedIntFromLong < 0
  		ifTrue:
+ 			[| cogMethod |
+ 			 "Since we would have to generate a machine-code method to be able to map
- 			["Since we would have to generate a machine-code method to be able to map
  			  the native pc anyway we should create a native method and native frame."
+ 			 cogMethod := self ensureMethodIsCogged: theMethod.
+ 			 theMethod := cogMethod asInteger.
- 			 self ensureMethodIsCogged: theMethod.
- 			 theMethod := (self cogMethodOf: theMethod) asInteger.
  			 maybeClosure ~= objectMemory nilObject
  				ifTrue:
  					["If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP = HasBeenReturnedFromMCPC signedIntFromLong
  						ifTrue:
  							[theMethod := (cogit findMethodForStartBcpc: (self startPCOfClosure: maybeClosure)
  												inHomeMethod: (self cCoerceSimple: theMethod
  																	to: #'CogMethod *')) asInteger.
  							 theMethod = 0 ifTrue:
  								[self error: 'cannot find machine code block matching closure''s startpc'].
  							 theIP := cogit ceCannotResumePC]
  						ifFalse:
  							[self assert: (theIP signedBitShift: -16) < -1. "See contextInstructionPointer:frame:"
  							 theMethod := theMethod - ((theIP signedBitShift: -16) * (cogit sizeof: CogBlockMethod)).
  							 theIP := theMethod - theIP signedIntFromShort].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						put: theMethod + MFMethodFlagHasContextFlag + MFMethodFlagIsBlockFlag]
  				ifFalse:
  					[self assert: (theIP signedBitShift: -16) >= -1.
  					 "If the pc is the special HasBeenReturnedFromMCPC pc set the pc
  					  appropriately so that the frame stays in the cannotReturn: state."
  					 theIP := theIP = HasBeenReturnedFromMCPC signedIntFromLong
  								ifTrue: [cogit ceCannotResumePC]
  								ifFalse: [theMethod asInteger - theIP].
  					 stackPages
  						longAt: (pointer := pointer - BytesPerWord)
  						put: theMethod + MFMethodFlagHasContextFlag].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext]
  		ifFalse:
  			[stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: theMethod.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: aContext.
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  			stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: 0. "FoxIFSavedIP"
  			theIP := self iframeInstructionPointerForIndex: theIP method: theMethod].
  	page baseFP: page headFP.
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (objectMemory fetchPointer: ReceiverIndex ofObject: aContext).
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"top of stack is the instruction pointer"
  	stackPages longAt: (pointer := pointer - BytesPerWord) put: theIP.
- 	self assert: (objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext)
- 			 = (self contextInstructionPointer: theIP frame: page baseFP).
  	page headSP: pointer.
+ 	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
  	self assert: self validStackPageBaseFrames.
  	^page!

Item was added:
+ ----- Method: CoInterpreter>>maybeTraceStackOverflow (in category 'debug support') -----
+ maybeTraceStackOverflow
+ 	cogit recordOverflowTrace ifTrue:
+ 		[self recordTrace: TraceStackOverflow
+ 			thing: TraceStackOverflow
+ 			source: ((self isMachineCodeFrame: framePointer)
+ 						ifTrue: [TraceIsFromMachineCode]
+ 						ifFalse: [TraceIsFromInterpreter])]!

Item was changed:
  ----- Method: CoInterpreter>>mustMapMachineCodePC:context: (in category 'frame access') -----
  mustMapMachineCodePC: theIP context: aOnceMarriedContext
  	"Map the native pc theIP into a bytecode pc integer object and answer it.
  	 See contextInstructionPointer:frame: for the explanation."
+ 	| maybeClosure methodObj cogMethod startBcpc bcpc |
- 	| maybeClosure methodObj startBcpc bcpc |
  	<inline: false>
+ 	<var: #cogMethod type: #'CogMethod *'>
  	theIP = HasBeenReturnedFromMCPC signedIntFromLong ifTrue:
  		[^objectMemory nilObject].
  	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aOnceMarriedContext.
  	methodObj := objectMemory fetchPointer: MethodIndex ofObject: aOnceMarriedContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue: [self assert: (theIP signedBitShift: -16) < -1.
  				startBcpc := self startPCOfClosure: maybeClosure]
  		ifFalse: [self assert: (theIP signedBitShift: -16) = -1.
  				startBcpc := self startPCOfMethod: methodObj].
+ 	cogMethod := self ensureMethodIsCogged: methodObj.
+ 	bcpc := self bytecodePCFor: theIP cogMethod: cogMethod startBcpc: startBcpc.
- 	self ensureMethodIsCogged: methodObj.
- 	bcpc := self bytecodePCFor: theIP cogMethod: (self cogMethodOf: methodObj) startBcpc: startBcpc.
  	self assert: bcpc >= (self startPCOfMethod: methodObj).
+ 	self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: "If there's a CallPrimitive we need to skip it."
+ 			[(bcpc = startBcpc
+ 			 and: [maybeClosure = objectMemory nilObject
+ 			 and: [self methodHeaderHasPrimitive: cogMethod methodHeader]]) ifTrue:
+ 				[bcpc := bcpc + (self sizeOfCallPrimitiveBytecode: cogMethod methodHeader)]].
  	^objectMemory integerObjectOf: bcpc + 1!

Item was changed:
  ----- Method: CoInterpreter>>printLogEntryAt: (in category 'debug support') -----
  printLogEntryAt: i
  	<inline: false>
  	| intOrClass selectorMethodOrProcess source |
  	intOrClass := traceLog at: i.
  	selectorMethodOrProcess := traceLog at: i + 1.
  	source := traceLog at: i + 2.
  	source <= TraceIsFromInterpreter ifTrue:
  		[self print: (traceSources at: source); space].
  	(objectMemory isIntegerObject: intOrClass)
  		ifTrue:
+ 			[intOrClass = TraceStackOverflow ifTrue:
+ 				[self print: 'stack overflow'].
+ 			 intOrClass = TraceContextSwitch ifTrue:
- 			[intOrClass = TraceContextSwitch ifTrue:
  				[self print: 'context switch from '; printHex: selectorMethodOrProcess].
  			 intOrClass = TraceBlockActivation ifTrue:
  				[self print: ' [] in '; printHex: selectorMethodOrProcess].
  			 intOrClass = TraceBlockCreation ifTrue:
  				[self print: 'create [] '; printHex: selectorMethodOrProcess].
  			 intOrClass = TraceIncrementalGC ifTrue:
  				[self print: 'incrementalGC'].
  			 intOrClass = TraceFullGC ifTrue:
  				[self print: 'fullGC'].
  			 intOrClass = TraceCodeCompaction ifTrue:
  				[self print: 'compactCode'].
  			 intOrClass = TraceVMCallback ifTrue:
  				[self print: 'callback'].
  			 intOrClass = TraceVMCallbackReturn ifTrue:
  				[self print: 'return from callback']]
  		ifFalse:
  			[self space; printNameOfClass: intOrClass count: 5; print: '>>'; printStringOf: selectorMethodOrProcess].
  	source > TraceIsFromInterpreter ifTrue:
  		[self space; print: (traceSources at: source)].
  	self cr!

Item was changed:
  ----- Method: CoInterpreter>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
+ validInstructionPointer: instrPointer inMethod: aMethod framePointer: fp
+ 	<var: #instrPointer type: #usqInt>
- validInstructionPointer: anInstrPointer inMethod: aMethod framePointer: fp
- 	<var: #anInstrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
  	<var: #fp type: #'char *'>
  	| theInstrPointer cogMethod |
  	<var: #theInstrPointer type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	instrPointer = cogit ceCannotResumePC ifTrue:
- 	anInstrPointer = cogit ceCannotResumePC ifTrue:
  		[^self isMachineCodeFrame: fp].
+ 	instrPointer = cogit ceReturnToInterpreterPC
- 	anInstrPointer = cogit ceReturnToInterpreterPC
  		ifTrue:
  			[(self isMachineCodeFrame: fp) ifTrue:
  				[^false].
  			 theInstrPointer := self iframeSavedIP: fp]
  		ifFalse:
+ 			[theInstrPointer := instrPointer.
- 			[theInstrPointer := anInstrPointer.
  			self cppIf: NewspeakVM
  				ifTrue:
  					[(self isMachineCodeFrame: fp) ifTrue:
  						[cogMethod := self mframeHomeMethod: fp.
  						 ^theInstrPointer >= (cogMethod asUnsignedInteger + (cogit sizeof: CogMethod))
  						   and: [theInstrPointer < (cogMethod asUnsignedInteger + cogMethod blockSize)]]]
  				ifFalse:
  					[| header |
  					 header := self rawHeaderOf: aMethod.
  					 ((self isCogMethodReference: header)
  					   and: [theInstrPointer < objectMemory startOfMemory]) ifTrue:
  					 	[cogMethod := self cCoerceSimple: header to: #'CogMethod *'.
  					 	 ^theInstrPointer >= (header + (cogit sizeof: CogMethod))
  					 	 and: [theInstrPointer < (header + cogMethod blockSize)]]]].
+ 	^super validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp!
- 	^theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerWord - 1)
- 	  and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + BaseHeaderSize)]!

Item was changed:
  ----- Method: CogVMSimulator>>ensureMethodIsCogged: (in category 'frame access') -----
  ensureMethodIsCogged: methodObj
  	"Uncomment this to compact frequently and hence test if clients are ready for the shock."
  	"[self commenceCogCompiledCodeCompaction]
  		on: Halt
  		do: [:ex| ex resume: nil]."
+ 	^super ensureMethodIsCogged: methodObj!
- 	super ensureMethodIsCogged: methodObj!

Item was changed:
  ----- Method: CogVMSimulator>>startInContextSuchThat: (in category 'simulation only') -----
  startInContextSuchThat: aBlock
  	"Change the active process's suspendedContext to its sender, which short-cuts the
  	 initialization of the system.  This can be a short-cut to running code, e.g. when doing
  		Smalltalk saveAs.
  		Compiler recompileAll
  	 via e.g.
  		vm startInContextSuchThat: [:ctxt| (vm stringOf: (vm penultimateLiteralOf: (vm methodForContext: ctxt))) = 'DoIt']"
  	<doNotGenerate>
  	| context activeProc |
  	activeProc := self activeProcess.
  	context := objectMemory fetchPointer: SuspendedContextIndex ofObject: activeProc.
  	[context = objectMemory nilObject ifTrue:
+ 		[^self error: 'no context found'].
- 		[self error: 'no context found'].
  	 aBlock value: context] whileFalse:
  		[context := objectMemory fetchPointer: SenderIndex ofObject: context].
  	objectMemory storePointer: SuspendedContextIndex ofObject: activeProc withValue: context.
  	"Now push a dummy return value."
  	objectMemory
  		storePointer: (self fetchStackPointerOf: context) + CtxtTempFrameStart
  		ofObject: context
  		withValue: objectMemory nilObject.
  	self storeInteger: StackPointerIndex
  		ofObject: context
  		withValue: (self fetchStackPointerOf: context) + 1!

Item was changed:
  ----- Method: Cogit>>breakOnImplicitReceiver (in category 'debugging') -----
  breakOnImplicitReceiver
  	<api>
+ 	<cmacro: '() (traceFlags & 64)'>
+ 	^(traceFlags bitAnd: 64) ~= 0!
- 	<cmacro: '() (traceFlags & 32)'>
- 	^(traceFlags bitAnd: 32) ~= 0!

Item was changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
+ 	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
- 	 The dynamic frequency of explicit outer is so low we merely cann an interpreter routine."
  	ceExplicitReceiverTrampoline := self genTrampolineFor: #ceExplicitReceiverAt: asSymbol
+ 										called: 'ceExplicitReceiverTrampoline'
+ 										arg: SendNumArgsReg
+ 										result: ReceiverResultReg.
- 												called: 'ceExplicitReceiverTrampoline'
- 												arg: SendNumArgsReg
- 												result: ReceiverResultReg.
  	"Cached push implicit receiver implementation.  Caller looks like
  				mov selector, ClassReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
  	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver, otherwise the mixin.
  	 Generate the class fetch and cache probe inline for speed. Smashes Arg0Reg and caller-saved regs."
  	opcodeIndex := 0.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	objectRepresentation genGetClassObjectOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
  	self MoveMw: 0 r: SPReg R: TempReg.
  	self MoveMw: backEnd jumpShortByteSize r: TempReg R: Arg0Reg.
  	self CmpR: ClassReg R: Arg0Reg.
  	jumpMiss := self JumpNonZero: 0.
  	self MoveMw: backEnd jumpShortByteSize + BytesPerOop r: TempReg R: ClassReg.
  	self CmpCq: 0 R: ClassReg.
  	jumpItsTheReceiverStupid := self JumpZero: 0.
  	self MoveR: ClassReg R: ReceiverResultReg.
  	jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  	jumpMiss jmpTarget: self Label.
  	ceImplicitReceiverTrampoline := self
  										genTrampolineFor: #ceImplicitReceiverFor:receiver:class: asSymbol
  										called: 'ceImplicitReceiverTrampoline'
  										callJumpBar: true
  										numArgs: 3
  										arg: SendNumArgsReg
  										arg: ReceiverResultReg
  										arg: ClassReg
  										arg: nil
  										saveRegs: false
  										resultReg: ReceiverResultReg
  										appendOpcodes: true!

Item was added:
+ ----- Method: Cogit>>recordOverflowTrace (in category 'debugging') -----
+ recordOverflowTrace
+ 	<api>
+ 	<cmacro: '() (traceFlags & 32)'>
+ 	^(traceFlags bitAnd: 32) ~= 0!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>longStoreBytecodeForHeader: (in category 'accessing') -----
+ longStoreBytecodeForHeader: methodHeaderOop
+ 	"Answer the relevant long store temp bytecode, which indicates it has a primitive error code."
+ 	"234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii"
+ 	"129 		10000001 jjkkkkkk 	Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk"
+ 	^(headerToMethodMap at: methodHeaderOop) usesAlternateBytecodeSet
+ 		ifTrue: [234]
+ 		ifFalse: [129]!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>methodHasErrorCode:header:initialIP: (in category 'accessing') -----
- methodHasErrorCode: aMethodObj header: methodHeaderOop initialIP: initialPC
- 	"Answer if the method starts with a long store temp bytecode, which indicates it has a primitive error code."
- 	"234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii"
- 	"129 		10000001 jjkkkkkk 	Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk"
- 	| method |
- 	method := self objectForOop: aMethodObj.
- 	self assert: method primitive > 0.
- 	self assert: method == (headerToMethodMap at: methodHeaderOop).
- 	^method usesAlternateBytecodeSet
- 		ifTrue:
- 			[(method byteAt: method initialPC + 3 "Skip CallPrimitive") = 234 "long store temp"]
- 		ifFalse:
- 			[(method byteAt: method initialPC) = 129 "long store (but can only be for a temp)"]!

Item was changed:
  ----- Method: NewObjectMemory>>longPrintReferencesTo: (in category 'debug printing') -----
  longPrintReferencesTo: anOop
  	"Scan the heap long printing the oops of any and all objects that refer to anOop"
  	| oop i prntObj |
  	<api>
  	prntObj := false.
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[((self isPointers: oop) or: [self isCompiledMethod: oop]) ifTrue:
  			[(self isCompiledMethod: oop)
  				ifTrue:
+ 					[i := self literalCountOf: oop]
- 					[i := (self literalCountOf: oop) - 1]
  				ifFalse:
+ 					[(coInterpreter isContext: oop)
+ 						ifTrue: [i := CtxtTempFrameStart + (coInterpreter fetchStackPointerOf: oop)]
+ 						ifFalse: [i := self lengthOf: oop]].
+ 			[(i := i - 1) >= 0] whileTrue:
- 					[(self isContext: oop)
- 						ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
- 						ifFalse: [i := (self lengthOf: oop) - 1]].
- 			[i >= 0] whileTrue:
  				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
  					[self printHex: oop; print: ' @ '; printNum: i; cr.
  					 prntObj := true.
+ 					 i := 0]].
- 					 i := 0].
- 				 i := i - 1].
  			prntObj ifTrue:
  				[prntObj := false.
  				 coInterpreter longPrintOop: oop]].
  		 oop := self accessibleObjectAfter: oop]!

Item was added:
+ ----- Method: NewObjectMemory>>printReferencesTo: (in category 'debug printing') -----
+ printReferencesTo: anOop
+ 	"Scan the heap printing the oops of any and all objects that refer to anOop"
+ 	| oop i |
+ 	<api>
+ 	oop := self firstAccessibleObject.
+ 	[oop = nil] whileFalse:
+ 		[((self isPointers: oop) or: [self isCompiledMethod: oop]) ifTrue:
+ 			[(self isCompiledMethod: oop)
+ 				ifTrue:
+ 					[i := self literalCountOf: oop]
+ 				ifFalse:
+ 					[(coInterpreter isContext: oop)
+ 						ifTrue: [i := CtxtTempFrameStart + (coInterpreter fetchStackPointerOf: oop)]
+ 						ifFalse: [i := self lengthOf: oop]].
+ 			[(i := i - 1) >= 0] whileTrue:
+ 				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
+ 					[self interpreter printHex: oop; print: ' @ '; printNum: i; space; printOopShort: oop; cr.
+ 					 i := 0]]].
+ 		 oop := self accessibleObjectAfter: oop]!

Item was changed:
  ----- Method: ObjectMemory>>printReferencesTo: (in category 'debug printing') -----
  printReferencesTo: anOop
  	"Scan the heap printing the oops of any and all objects that refer to anOop"
  	| oop i |
  	<api>
  	oop := self firstAccessibleObject.
  	[oop = nil] whileFalse:
  		[((self isPointers: oop) or: [self isCompiledMethod: oop]) ifTrue:
  			[(self isCompiledMethod: oop)
  				ifTrue:
+ 					[i := self literalCountOf: oop]
- 					[i := (self literalCountOf: oop) - 1]
  				ifFalse:
  					[(self isContext: oop)
+ 						ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop)]
+ 						ifFalse: [i := self lengthOf: oop]].
+ 			[(i := i - 1) >= 0] whileTrue:
- 						ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
- 						ifFalse: [i := (self lengthOf: oop) - 1]].
- 			[i >= 0] whileTrue:
  				[anOop = (self fetchPointer: i ofObject: oop) ifTrue:
  					[self interpreter printHex: oop; print: ' @ '; printNum: i; space; printOopShort: oop; cr.
+ 					 i := 0]]].
- 					 i := 0].
- 				 i := i - 1]].
  		 oop := self accessibleObjectAfter: oop]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileFrameBuild (in category 'compile abstract instructions') -----
  compileFrameBuild
  	"Build a frame for a CogMethod activation.  See CoInterpreter class>>initializeFrameIndices.
  	 		receiver (in ReceiverResultReg)
  			arg0
  			...
  			argN
  			caller's saved ip/this stackPage (for a base frame)
  	fp->	saved fp
  			method
  			context (uninitialized?)
  			receiver
  			first temp
  			...
  	sp->	Nth temp
  	If there is a primitive and an error code the Nth temp is the error code.
  	Ensure SendNumArgsReg is set early on (incidentally to nilObj) because
  	it is the flag determining whether context switch is allowed on stack-overflow."
  	| methodHeader jumpSkip |
  	<inline: false>
  	<var: #jumpSkip type: #'AbstractInstruction *'>
  	needsFrame ifFalse: [^0].
  	methodHeader := coInterpreter headerOf: methodObj.
  	self PushR: FPReg.
  	self MoveR: SPReg R: FPReg.
  	methodLabel addDependent: (self annotateAbsolutePCRef:
  		(self PushCw: methodLabel asInteger)). "method"
  	self annotate: (self MoveCw: objectMemory nilObject R: SendNumArgsReg)
  		objRef: objectMemory nilObject.
  	self PushR: SendNumArgsReg. "context"
  	self PushR: ReceiverResultReg.
  	methodOrBlockNumArgs + 1 to: (coInterpreter tempCountOf: methodObj) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(primitiveIndex > 0
+ 	 and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
+ 			= (objectMemory
+ 				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
+ 				ofObject: methodObj)]) ifTrue:
- 	 and: [(coInterpreter
- 			methodHasErrorCode: methodObj
- 			header: methodHeader
- 			initialIP: (self pointerForOop: (coInterpreter
- 											initialPCForHeader: methodHeader
- 											method: methodObj)))]) ifTrue:
  		[self compileGetErrorCode.
  		 initialPC := initialPC
  				   + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
  				   + (coInterpreter sizeOfLongStoreTempBytecode: methodHeader)].
  	self MoveAw: coInterpreter stackLimitAddress R: TempReg.
  	self CmpR: TempReg R: SPReg. "N.B. FLAGS := SPReg - TempReg"
  	"If we can't context switch for this method, use a slightly
  	 slower overflow check that clears SendNumArgsReg."
  	(coInterpreter canContextSwitchIfActivating: methodObj header: methodHeader)
  		ifTrue:
  			[self JumpBelow: stackOverflowCall.
  			 stackCheckLabel := self Label]
  		ifFalse:
  			[jumpSkip := self JumpAboveOrEqual: 0.
  			 self MoveCq: 0 R: SendNumArgsReg.
  			 self Jump: stackOverflowCall.
  			 jumpSkip jmpTarget: (stackCheckLabel := self Label)].
  	self annotateBytecode: stackCheckLabel!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genJumpIf:to: (in category 'bytecode generators') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half."
  	<inline: false>
  	| desc fixup ok counter countTripped retry |
  	<var: #desc type: #'CogSimStackEntry *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #counter type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 1.
  	desc := self ssTop.
  	self ssPop: 1.
  	(desc type == SSConstant
  	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
  		["Must arrange there's a fixup at the target whether it is jumped to or
  		  not so that the simStackPtr can be kept correct."
  		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
  		 "Must enter any annotatedConstants into the map"
+ 		 self annotateBytecodeIfAnnotated: desc.
- 		 desc annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
  		 "Must annotate the bytecode for correct pc mapping."
  		 self annotateBytecode: (desc constant = boolean
  									ifTrue: [self Jump: fixup]
  									ifFalse: [self prevInstIsPCAnnotated
  												ifTrue: [self Nop]
  												ifFalse: [self Label]]).
  		 ^0].
  	desc popToReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counter := self addressOf: (counters at: counterIndex).
  	counterIndex := counterIndex + 1.
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
  	retry := counter addDependent: (self annotateAbsolutePCRef:
  				(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"Don't write back if we trip; avoids wrapping count back to initial value, and if we trip we don't execute."
  	countTripped := self JumpCarry: 0.
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	"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."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self SubCq: 1 R: SendNumArgsReg. "Count untaken"
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if SendNumArgsReg is 0 this is a mustBeBoolean, not a counter trip."
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
  	self CmpCq: 0 R: TempReg.
  	self JumpNonZero: retry.
  	ok jmpTarget: (self annotateBytecode: self Label).
  	^0!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst counter countTripped |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #counter type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
+ 		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
+ 		 self annotateBytecodeIfAnnotated: self ssTop.
- 		 (self ssValue: 1) annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
- 		 self ssTop annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	self ssAllocateRequiredReg: SendNumArgsReg. "Use this as the count reg."
  	counter := self addressOf: (counters at: counterIndex).
  	self flag: 'will need to use MoveAw32:R: if 64 bits'.
  	self assert: BytesPerWord = CounterBytes.
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveAw: counter asUnsignedInteger R: SendNumArgsReg)).
  	self SubCq: 16r10000 R: SendNumArgsReg. "Count executed"
  	"If counter trips simply abort the inlined comparison and send continuing to the following
  	 branch *without* writing back.  A double decrement will not trip the second time."
  	countTripped := self JumpCarry: 0.
  	counter addDependent: (self annotateAbsolutePCRef:
  		(self MoveR: SendNumArgsReg Aw: counter asUnsignedInteger)). "write back"
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1!

Item was added:
+ ----- Method: StackInterpreter>>context:hasValidInversePCMappingOf:in: (in category 'debug support') -----
+ context: aContext hasValidInversePCMappingOf: theIP in: theFP
+ 	"For asserts.  Check that theIP maps back correctly to the context's pc.
+ 	 The CallPrimitive bytecode presents a complication."
+ 	| pc encodedip |
+ 	<var: #theFP type: #'char *'>
+ 	pc := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
+ 	encodedip := self contextInstructionPointer: theIP frame: theFP.
+ 	^self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [pc = encodedip
+ 				or: [| methodHeader |
+ 					methodHeader := self headerOf: (objectMemory fetchPointer: MethodIndex ofObject: aContext).
+ 					(self methodHeaderHasPrimitive: methodHeader)
+ 					and: [(objectMemory integerValueOf: encodedip) - (objectMemory integerValueOf: pc)
+ 						= (self sizeOfCallPrimitiveBytecode: methodHeader)]]]
+ 		ifFalse: [pc = encodedip]!

Item was removed:
- ----- Method: StackInterpreter>>frameInstructionPointerForContext:method: (in category 'frame access') -----
- frameInstructionPointerForContext: aContext method: aMethod
- 	"Answer the instruction pointer for usage in a frame (a pointer to a bytecode)
- 	 from the index instructionPointer in the given context."
- 	^aMethod
- 	+ (self quickFetchInteger: InstructionPointerIndex ofObject: aContext)
- 	+ BaseHeaderSize
- 	- 2!

Item was changed:
  ----- Method: StackInterpreter>>handleStackOverflow (in category 'message sending') -----
  handleStackOverflow
  	"Check for stack overflow, moving frames to another stack if so."
  	| newPage theFP callerFP overflowLimitAddress overflowCount |
  	<var: #newPage type: #'StackPage *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #overflowLimitAddress type: #'char *'>
  
  	"After checkForInterrupts another event check may have been forced, setting both
  	 stackLimit and stackPage stackLimit to all ones.  So here we must check against
  	 the real stackLimit, not the effective stackLimit."
  	stackPointer < stackPage realStackLimit ifFalse:
  		[^self].
  
+ 	self maybeTraceStackOverflow.
  	statStackOverflow := statStackOverflow + 1.
  
  	"The stack has overflowed this page.  If the system is executing some recursive algorithm,
  	 e.g. fibonacci, then the system could thrash overflowing the stack if the call soon returns
  	 back to the current page.  To avoid thrashing, since overflow is quite slow, we can move
  	 more than one frame.  The idea is to record which page has overflowed, and the first
  	 time it overflows move one frame, the second time two frames, and so on.  We move no
  	 more frames than would leave the page half occupied."
  	theFP := framePointer.
  	stackPage = overflowedPage
  		ifTrue:
  			[overflowLimitAddress := stackPage baseAddress - stackPages overflowLimit.
  			 overflowCount := extraFramesToMoveOnOverflow := extraFramesToMoveOnOverflow + 1.
  			 [(overflowCount := overflowCount - 1) >= 0
  			   and: [(callerFP := self frameCallerFP: theFP) < overflowLimitAddress
  			   and: [(self isBaseFrame: callerFP) not]]] whileTrue:
  				[theFP := callerFP]]
  		ifFalse:
  			[overflowedPage := stackPage.
  			 extraFramesToMoveOnOverflow := 0].
  
  	self ensureCallerContext: theFP.
  	newPage := self newStackPage.
  	self moveFramesIn: stackPage through: theFP toPage: newPage.
  	self setStackPageAndLimit: newPage.
  	framePointer := stackPage headFP.
  	stackPointer := stackPage headSP.
  	self isCog
  		ifFalse: "To overflow the stack this must be a new frame, but in Cog base frames are married."
  			[self assert: (self frameHasContext: framePointer) not.
  			 self assert: (self validInstructionPointer: instructionPointer
  							inMethod: method
  							framePointer: framePointer)]
  		ifTrue:
  			[self assert: (self validInstructionPointer: instructionPointer
  							inFrame: framePointer).
  			 self assert: ((self frameHasContext: framePointer) not
  						or: [self isContext: (self frameContext: framePointer)])]!

Item was added:
+ ----- Method: StackInterpreter>>iframeInstructionPointerForIndex:method: (in category 'frame access') -----
+ iframeInstructionPointerForIndex: ip method: aMethod
+ 	"Answer the instruction pointer for use in an interpreter frame (a pointer to a bytecode)."
+ 	self assert: (ip between: (objectMemory lastPointerOf: aMethod) and: (objectMemory lengthOf: aMethod)).
+ 	^aMethod + ip + BaseHeaderSize - 2!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode |
  	<inline: true>
  
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
+ 	self setMethod: newMethod methodHeader: methodHeader.
- 	self setMethod: newMethod.
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: localIP + 1)
+ 			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method
- 		  starts with a long store temp.  Strictly no need to skip the store because it's a noop."
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: localIP + 1) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0].
- 		localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader)].
  
  	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: StackInterpreter>>isNullExternalPrimitiveCall: (in category 'compiled methods') -----
  isNullExternalPrimitiveCall: aMethodObj
  	"Answer if the method is an external primtiive call (prim 117) with a null external primtiive.
  	 This is just for an assert in the CoInterpreter."
  	| lit |
  	((self primitiveIndexOf: aMethodObj) = 117
  	and: [(self literalCountOf: aMethodObj) > 0]) ifFalse:
  		[^false].
  
  	lit := self literal: 0 ofMethod: aMethodObj.
  	^(objectMemory isArray: lit)
  	  and: [(objectMemory lengthOf: lit) = 4
+ 	  and: [(objectMemory fetchPointer: 3 ofObject: lit) = ConstZero
+ 			or: [(objectMemory fetchPointer: 3 ofObject: lit) = ConstMinusOne]]]!
- 	  and: [(objectMemory fetchPointer: 3 ofObject: lit) = ConstZero]]!

Item was changed:
  ----- Method: StackInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode |
  	<inline: true>
  	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	numArgs := self argumentCountOfMethodHeader: methodHeader.
  
  	rcvr := self stackValue: numArgs. "could new rcvr be set at point of send?"
  
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: newMethod.
+ 	self setMethod: newMethod methodHeader: methodHeader.
- 	self setMethod: newMethod.
  	self push: (self encodeFrameFieldHasContext: false isBlock: false numArgs: numArgs).
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: rcvr.
  
  	"clear remaining temps to nil"
  	numArgs+1 to: numTemps do:
  		[:i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
+ 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
+ 		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
+ 		 instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader).
+ 		 primFailCode ~= 0 ifTrue:
+ 			[(objectMemory byteAt: instructionPointer + 1)
+ 			  = (self longStoreBytecodeForHeader: methodHeader) ifTrue:
- 		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method
- 		  starts with a long store temp.  Strictly no need to skip the store because it's a noop."
- 		(self methodHasErrorCode: newMethod header: methodHeader initialIP: instructionPointer + 1) ifTrue:
- 			[primFailCode ~= 0 ifTrue:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
+ 			 primFailCode := 0]].
- 				 primFailCode := 0].
- 		instructionPointer := instructionPointer + (self sizeOfCallPrimitiveBytecode: methodHeader)].
  
  	^methodHeader!

Item was changed:
  ----- Method: StackInterpreter>>longPrintOop: (in category 'debug printing') -----
  longPrintOop: oop
  	<api>
  	| fmt lastIndex startIP bytecodesPerLine column |
  	((objectMemory isIntegerObject: oop)
  	 or: [(oop between: objectMemory startOfMemory and: objectMemory freeStart) not
  	 or: [(oop bitAnd: (BytesPerWord - 1)) ~= 0
  	 or: [(objectMemory isFreeObject: oop)
  	 or: [(fmt := objectMemory formatOf: oop) between: 5 and: 11]]]]) ifTrue:
  		[^self printOop: oop].
  	self printHex: oop;
  		print: ': a(n) ';
  		printNameOfClass: (objectMemory fetchClassOfNonInt: oop) count: 5.
  	fmt > 4 ifTrue:
  		[self print: ' nbytes '; printNum: (objectMemory byteSizeOf: oop)].
  	self cr.
  	lastIndex := 256 min: (startIP := (objectMemory lastPointerOf: oop) / BytesPerWord).
  	lastIndex > 0 ifTrue:
  		[1 to: lastIndex do:
  			[:i| | fieldOop |
  			fieldOop := objectMemory fetchPointer: i - 1 ofObject: oop.
  			self space; printNum: i - 1; space; printHex: fieldOop; space.
  			(i = 1 and: [objectMemory isCompiledMethod: oop])
  				ifTrue: [self printMethodHeaderOop: fieldOop]
  				ifFalse: [self printOopShort: fieldOop].
  			self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > 64 ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := startIP * BytesPerWord + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 100 ifTrue:
  				[lastIndex := startIP + 100].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
+ 					[self cCode: 'printf("0x%08x: ", oop+BaseHeaderSize+index-1)'
+ 						inSmalltalk: [self print: (oop+BaseHeaderSize+index-1) hex; print: ': ']].
- 					[self cCode: 'printf("%08x: ", oop+index-1)'
- 						inSmalltalk: [self print: (oop+index-1) hex; print: ': ']].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
  				self cCode: 'printf(" %02x/%-3d", byte,byte)'
  					inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte].
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			column = 1 ifFalse:
  				[self cr]]!

Item was added:
+ ----- Method: StackInterpreter>>longStoreBytecodeForHeader: (in category 'compiled methods') -----
+ longStoreBytecodeForHeader: methodHeader
+ 	"Answer the relevant long store temp bytecode, which indicates it has a primitive error code."
+ 	"234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii"
+ 	"129 		10000001 jjkkkkkk 	Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk"
+ 	<api>
+ 	<inline: true>
+ 	^self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [(self headerIndicatesAlternateBytecodeSet: methodHeader) ifTrue: [234] ifFalse: [129]]
+ 		ifFalse: [129]!

Item was changed:
  ----- Method: StackInterpreter>>makeBaseFrameFor: (in category 'frame access') -----
  makeBaseFrameFor: aContext "<Integer>"
+ 	"Marry aContext with the base frame of a new stack page.  Build the base
+ 	 frame to reflect the context's state.  Answer the new page."
+ 	<returnTypeC: #'StackPage *'>
+ 	| page pointer theMethod theIP numArgs stackPtrIndex maybeClosure |
- 	"Marry aContext with the base frame of a new stack page.  Build
- 	 the base frame to reflect the context's state.  Answer the new page."
- 	| page pointer theMethod numArgs stackPtrIndex maybeClosure |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
- 	<returnTypeC: 'StackPage *'>
  	self assert: (self isSingleContext: aContext).
  	page := self newStackPage.
  	pointer := page baseAddress.
+ 	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	theMethod := objectMemory fetchPointer: MethodIndex ofObject: aContext.
+ 	(objectMemory isIntegerObject: theIP) ifFalse:
+ 		[self error: 'context is not resumable'].
+ 	theIP := objectMemory integerValueOf: theIP.
  	"If the frame is a closure activation then the closure should be on the stack in
  	 the pushed receiver position (closures receiver the value[:value:] messages).
  	 Otherwise it should be the receiver proper."
+ 	maybeClosure := objectMemory fetchPointer: ClosureIndex ofObject: aContext.
- 	maybeClosure := (objectMemory fetchPointer: ClosureIndex ofObject: aContext).
  	maybeClosure ~= objectMemory nilObject
+ 		ifTrue:
+ 			[numArgs := self argumentCountOfClosure: maybeClosure.
- 		ifTrue: [numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
+ 			[| header |
+ 			 header := self headerOf: theMethod.
+ 			 numArgs := self argumentCountOfMethodHeader: header.
+ 			 self cppIf: MULTIPLEBYTECODESETS
+ 				ifTrue: "If this is a synthetic context its IP could be pointing at the CallPrimitive opcode.  If so, skip it."
+ 					[(theIP signedIntFromLong > 0
+ 					  and: [(self methodHeaderHasPrimitive: header)
+ 					  and: [theIP = (1 + (objectMemory lastPointerOf: theMethod))]]) ifTrue:
+ 						[theIP := theIP + (self sizeOfCallPrimitiveBytecode: header)]].
- 			[numArgs := self argumentCountOf: theMethod.
  			 stackPages longAt: pointer put: (objectMemory fetchPointer: ReceiverIndex ofObject: aContext)].
  	"Put the arguments on the stack"
  	1 to: numArgs do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
  	"saved caller ip is sender context in base frame"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (objectMemory fetchPointer: SenderIndex ofObject: aContext).
  	"base frame's saved fp is null"
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: 0.
  	page baseFP: pointer; headFP: pointer.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: theMethod.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (self encodeFrameFieldHasContext: true isBlock: maybeClosure ~= objectMemory nilObject numArgs: numArgs).
  	self assert: (self frameHasContext: page baseFP).
  	self assert: (self frameNumArgs: page baseFP) == numArgs.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: aContext.
  	stackPages
  		longAt: (pointer := pointer - BytesPerWord)
  		put: (objectMemory fetchPointer: ReceiverIndex ofObject: aContext).
  	stackPtrIndex := self quickFetchInteger: StackPointerIndex ofObject: aContext.
  	self assert: ReceiverIndex + stackPtrIndex < (objectMemory lengthOf: aContext).
  	numArgs + 1 to: stackPtrIndex do:
  		[:i|
  		stackPages
  			longAt: (pointer := pointer - BytesPerWord)
  			put: (objectMemory fetchPointer: ReceiverIndex + i ofObject: aContext)].
+ 	"top of stack is the instruction pointer"
+ 	theIP := self iframeInstructionPointerForIndex: theIP method: theMethod.
+ 	stackPages longAt: (pointer := pointer - BytesPerWord) put: theIP.
- 	"last thing on stack is the instruction pointer"
- 	(objectMemory isIntegerObject: (objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext)) ifFalse:
- 		[self error: 'context is not resumable'].
- 	stackPages
- 		longAt: (pointer := pointer - BytesPerWord)
- 		put: (self frameInstructionPointerForContext: aContext method: theMethod).
- 	self assert: (objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext)
- 			= (self contextInstructionPointer: (stackPages longAt: pointer) frame: page baseFP).
  	page headSP: pointer.
+ 	self assert: (self context: aContext hasValidInversePCMappingOf: theIP in: page baseFP).
  
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
+ 	 w.r.t. the frame when we check for validity) plus SmallInteger tags."
- 	 w.r.t. the frame when we check for validity)"
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: page baseFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: aContext
  		withValue: (self withSmallIntegerTags: 0).
  	self assert: (objectMemory isIntegerObject: (objectMemory fetchPointer: SenderIndex ofObject: aContext)).
  	self assert: (self frameOfMarriedContext: aContext) = page baseFP.
+ 	self assert: self validStackPageBaseFrames.
- 
  	^page!

Item was added:
+ ----- Method: StackInterpreter>>maybeTraceStackOverflow (in category 'debug support') -----
+ maybeTraceStackOverflow
+ 	"nop in the stack interpreter"!

Item was removed:
- ----- Method: StackInterpreter>>methodHasErrorCode:header:initialIP: (in category 'compiled methods') -----
- methodHasErrorCode: aMethodObj header: methodHeader initialIP: initialPC
- 	"Answer if the method starts with a long store temp bytecode, which indicates it has a primitive error code."
- 	"234		11101010	i i i i i i i i	Store Temporary Variable #iiiiiiii"
- 	"129 		10000001 jjkkkkkk 	Store (Receiver Variable, Temporary Location, Illegal, Literal Variable) [jj] #kkkkkk"
- 	<api>
- 	<inline: true>
- 	<var: #initialPC type: #'char *'>
- 	^self
- 		cppIf: MULTIPLEBYTECODESETS
- 		ifTrue:
- 			[(self headerIndicatesAlternateBytecodeSet: methodHeader)
- 				ifTrue:
- 					[(objectMemory byteAt: initialPC + 3 "Skip CallPrimitive") = 234 "long store temp"]
- 				ifFalse:
- 					[(objectMemory byteAt: initialPC) = 129 "long store (but can only be for a temp)"]]
- 		ifFalse:
- 			[(objectMemory byteAt: initialPC) = 129 "long store (but can only be for a temp)"]!

Item was added:
+ ----- Method: StackInterpreter>>noAssertHeaderOf: (in category 'compiled methods') -----
+ noAssertHeaderOf: methodPointer
+ 	^objectMemory fetchPointer: HeaderIndex ofObject: methodPointer!

Item was changed:
  ----- Method: StackInterpreter>>printOop: (in category 'debug printing') -----
  printOop: oop
  	| cls fmt lastIndex startIP bytecodesPerLine column |
  	<inline: false>
  	self printHex: oop.
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^self
  			cCode: 'printf("=%ld\n", (long)integerValueOf(oop))'
  			inSmalltalk: [self print: (self shortPrint: oop); cr]].
  	(oop between: objectMemory startOfMemory and: objectMemory freeStart) ifFalse:
  		[self print: ' is not on the heap'; cr.
  		 ^nil].
  	(oop bitAnd: (BytesPerWord - 1)) ~= 0 ifTrue:
  		[self print: ' is misaligned'; cr.
  		 ^nil].
  	(objectMemory isFreeObject: oop) ifTrue:
  		[self print: ' is a free chunk of size '; printNum: (objectMemory sizeOfFree: oop); cr.
  		 ^nil].
  	self print: ': a(n) '.
  	self printNameOfClass: (cls := objectMemory fetchClassOfNonInt: oop) count: 5.
  	cls = (objectMemory splObj: ClassFloat) ifTrue:
  		[self cr; printFloat: (self dbgFloatValueOf: oop); cr.
  		 ^nil].
  	fmt := objectMemory formatOf: oop.
  	fmt > 4 ifTrue:
  		[self print: ' nbytes '; printNum: (objectMemory byteSizeOf: oop)].
  	self cr.
  	(fmt > 4 and: [fmt < 12]) ifTrue:
  		["This will answer false if splObj: ClassAlien is nilObject"
  		 (self is: oop KindOfClass: (objectMemory splObj: ClassAlien)) ifTrue:
  			[self print: ' datasize '; printNum: (self sizeOfAlienData: oop).
  			self print: ((self isIndirectAlien: oop)
  							ifTrue: [' indirect @ ']
  							ifFalse:
  								[(self isPointerAlien: oop)
  									ifTrue: [' pointer @ ']
  									ifFalse: [' direct @ ']]).
  			 self printHex: (self startOfAlienData: oop) asUnsignedInteger; cr.
  			 ^nil].
  		 (objectMemory isWords: oop) ifTrue:
  			[lastIndex := 64 min: ((objectMemory byteSizeOf: oop) / BytesPerWord).
  			 lastIndex > 0 ifTrue:
  				[1 to: lastIndex do:
  					[:index|
  					self space; printHex: (objectMemory fetchLong32: index - 1 ofObject: oop).
  					(index \\ self elementsPerPrintOopLine) = 0 ifTrue:
  						[self cr]].
  				(lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse:
  					[self cr]].
  			^nil].
  		^self printStringOf: oop; cr].
  	lastIndex := 64 min: (startIP := (objectMemory lastPointerOf: oop) / BytesPerWord).
  	lastIndex > 0 ifTrue:
  		[1 to: lastIndex do:
  			[:index|
  			self cCode: [self printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space]
  				inSmalltalk: [self space; printHex: (objectMemory fetchPointer: index - 1 ofObject: oop); space.
  							 self print: (self shortPrint: (objectMemory fetchPointer: index - 1 ofObject: oop))].
  			(index \\ self elementsPerPrintOopLine) = 0 ifTrue:
  				[self cr]].
  		(lastIndex \\ self elementsPerPrintOopLine) = 0 ifFalse:
  			[self cr]].
  	(objectMemory isCompiledMethod: oop)
  		ifFalse:
  			[startIP > 64 ifTrue: [self print: '...'; cr]]
  		ifTrue:
  			[startIP := startIP * BytesPerWord + 1.
  			 lastIndex := objectMemory lengthOf: oop.
  			 lastIndex - startIP > 100 ifTrue:
  				[lastIndex := startIP + 100].
  			 bytecodesPerLine := 8.
  			 column := 1.
  			 startIP to: lastIndex do:
  				[:index| | byte |
  				column = 1 ifTrue:
+ 					[self cCode: 'printf("0x%08x: ", oop+BaseHeaderSize+index-1)'
+ 						inSmalltalk: [self print: (oop+BaseHeaderSize+index-1) hex; print: ': ']].
- 					[self cCode: 'printf("%08x: ", oop+index-1)'
- 						inSmalltalk: [self print: (oop+index-1) hex; print: ': ']].
  				byte := objectMemory fetchByte: index - 1 ofObject: oop.
  				self cCode: 'printf(" %02x/%-3d", byte,byte)'
  					inSmalltalk: [self space; print: (byte radix: 16); printChar: $/; printNum: byte].
  				column := column + 1.
  				column > bytecodesPerLine ifTrue:
  					[column := 1. self cr]].
  			column = 1 ifFalse:
  				[self cr]]!

Item was changed:
  ----- Method: StackInterpreter>>printStringOf: (in category 'debug printing') -----
  printStringOf: oop
+ 	| fmt len cnt max i |
- 	| fmt cnt i |
  	<inline: false>
  	(objectMemory isIntegerObject: oop) ifTrue:
  		[^nil].
  	(oop between: objectMemory startOfMemory and: objectMemory freeStart) ifFalse:
  		[^nil].
+ 	(oop bitAnd: (BytesPerOop - 1)) ~= 0 ifTrue:
- 	(oop bitAnd: (BytesPerWord - 1)) ~= 0 ifTrue:
  		[^nil].
  	fmt := objectMemory formatOf: oop.
+ 	fmt < 8 ifTrue: [^nil].
- 	fmt < 8 ifTrue: [ ^nil ].
  
+ 	cnt := (max := 128) min: (len := objectMemory lengthOf: oop).
- 	cnt := 100 min: (objectMemory lengthOf: oop).
  	i := 0.
  
  	((objectMemory is: oop
  		  instanceOf: (objectMemory splObj: ClassByteArray)
  		  compactClassIndex: classByteArrayCompactIndex)
  	or: [(objectMemory is: oop
  			instanceOf: (objectMemory splObj: ClassLargePositiveInteger)
  			compactClassIndex: ClassLargePositiveIntegerCompactIndex)
  	or: [(objectMemory is: oop
  			instanceOf: (objectMemory splObj: ClassLargeNegativeInteger)
  			compactClassIndex: ClassLargeNegativeIntegerCompactIndex)]])
  		ifTrue:
+ 			[[i < cnt] whileTrue:
+ 				[self printHex: (objectMemory fetchByte: i ofObject: oop).
+ 				 i := i + 1]]
- 			[[i < cnt] whileTrue: [
- 				self printHex: (objectMemory fetchByte: i ofObject: oop).
- 				i := i + 1]]
  		ifFalse:
+ 			[[i < cnt] whileTrue:
+ 				[self printChar: (objectMemory fetchByte: i ofObject: oop).
+ 				 i := i + 1]].
+ 	len > max ifTrue:
+ 		[self print: '...'].
- 			[[i < cnt] whileTrue: [
- 				self printChar: (objectMemory fetchByte: i ofObject: oop).
- 				i := i + 1]].
  	self flush!

Item was added:
+ ----- Method: StackInterpreter>>setMethod:methodHeader: (in category 'internal interpreter access') -----
+ setMethod: aMethodObj methodHeader: methodHeader
+ 	"Set the method and determine the bytecode set based on the method header's sign.
+ 	 If MULTIPLEBYTECODESETS then a negative header selects the alternate bytecode set.
+ 	 Conditionalizing the code on MULTIPLEBYTECODESETS allows the header sign bit to be
+ 	 used for other experiments."
+ 	<inline: true>
+ 	method := aMethodObj.
+ 	self assert: (objectMemory isOopCompiledMethod: method).
+ 	self assert: (self headerOf: method) = methodHeader.
+ 	self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [bytecodeSetSelector := (self headerIndicatesAlternateBytecodeSet: methodHeader)
+ 											ifTrue: [256]
+ 											ifFalse: [0]]!

Item was changed:
  ----- Method: StackInterpreter>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
+ validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp
+ 	<var: #theInstrPointer type: #usqInt>
- validInstructionPointer: instrPointer inMethod: aMethod framePointer: fp
- 	<var: #instrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
+ 	^self
+ 		cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue:
+ 			[| methodHeader |
+ 			 methodHeader := self noAssertHeaderOf: aMethod. "-1 for pre-increment in fetchNextBytecode"
+ 			 theInstrPointer >= (aMethod + (self lastPointerOf: aMethod) + BaseHeaderSize - 1)
+ 			 and: [theInstrPointer < (aMethod + (self byteLengthOf: aMethod) + BaseHeaderSize - 1)
+ 			 and: ["If the method starts with a CallPrimitive opcode the instruction pointer should be past it."
+ 				((self headerIndicatesAlternateBytecodeSet: methodHeader)
+ 				and: [(self methodHeaderHasPrimitive: methodHeader)
+ 				and: [theInstrPointer < (aMethod
+ 										+ BaseHeaderSize - 1
+ 										+ (self lastPointerOf: aMethod)
+ 										+ (self sizeOfCallPrimitiveBytecode: methodHeader) - 1)]])
+ 					not]]]
+ 		ifFalse: "-1 for pre-increment in fetchNextBytecode"
+ 			[theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BaseHeaderSize - 1)
+ 			 and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + BaseHeaderSize - 1)]]!
- 	^instrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerWord - 1)
- 	  and: [instrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + BaseHeaderSize)]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>annotateBytecodeIfAnnotated: (in category 'bytecode generators') -----
+ annotateBytecodeIfAnnotated: aSimStackEntry
+ 	<var: #aSimStackEntry type: #'SimStackEntry'>
+ 	<inline: false>
+ 	aSimStackEntry annotateUse ifTrue:
+ 		[self annotateBytecode: (self prevInstIsPCAnnotated
+ 									ifTrue: [self Nop]
+ 									ifFalse: [self Label]).
+ 		 aSimStackEntry annotateUse: false]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPopStackBytecode (in category 'bytecode generators') -----
  genPopStackBytecode
+ 	self annotateBytecodeIfAnnotated: self ssTop.
  	self ssTop spilled ifTrue:
  		[self AddCq: BytesPerWord R: SPReg].
  	self ssPop: 1.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorArithmetic (in category 'bytecode generators') -----
  genSpecialSelectorArithmetic
  	| primDescriptor rcvrIsConst argIsConst rcvrIsInt argIsInt rcvrInt argInt result
  	 jumpNotSmallInts jumpContinue annotateInst instToAnnotate |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #jumpContinue type: #'AbstractInstruction *'>
  	<var: #instToAnnotate type: #'AbstractInstruction *'>
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := (argIsConst := self ssTop type = SSConstant)
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (rcvrIsConst := (self ssValue: 1) type = SSConstant)
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[rcvrInt := objectMemory integerValueOf: rcvrInt.
  		 argInt := objectMemory integerValueOf: argInt.
  		 primDescriptor opcode caseOf: {
  			[AddRR]	-> [result := rcvrInt + argInt].
  			[SubRR]	-> [result := rcvrInt - argInt].
  			[AndRR]	-> [result := rcvrInt bitAnd: argInt].
  			[OrRR]	-> [result := rcvrInt bitOr: argInt] }.
  		(objectMemory isIntegerValue: result) ifTrue:
  			["Must enter any annotatedConstants into the map"
+ 			 self annotateBytecodeIfAnnotated: (self ssValue: 1).
+ 			 self annotateBytecodeIfAnnotated: self ssTop.
- 			 (self ssValue: 1) annotateUse ifTrue:
- 				[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
- 			 self ssTop annotateUse ifTrue:
- 				[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
  			 "Must annotate the bytecode for correct pc mapping."
  			^self ssPop: 2; ssPushAnnotatedConstant: (objectMemory integerObjectOf: result)].
  		^self genSpecialSelectorSend].
  
  	"If there's any constant involved other than a SmallInteger don't attempt to inline."
  	((rcvrIsConst and: [rcvrIsInt not])
  	 or: [argIsConst and: [argIsInt not]]) ifTrue:
  		[^self genSpecialSelectorSend].
  
  	"If we know nothing about the types then better not to inline as the inline cache and
  	 primitive code is not terribly slow so wasting time on duplicating tag tests is pointless."
  	(argIsInt or: [rcvrIsInt]) ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[self ssFlushTo: simStackPtr - 2.
  			 (self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	primDescriptor opcode caseOf: {
  		[AddRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self AddCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self SubCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ReceiverResultReg.
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							jumpContinue := self JumpNoOverflow: 0.
  							"overflow; must undo the damage before continuing"
  							 rcvrIsInt
  								ifTrue: [self MoveCq: rcvrInt R: ReceiverResultReg]
  								ifFalse:
  									[self SubR: Arg0Reg R: ReceiverResultReg.
  									 objectRepresentation genSetSmallIntegerTagsIn: ReceiverResultReg]]].
  		[SubRR] -> [argIsInt
  						ifTrue:
  							[instToAnnotate := self SubCq: argInt - ConstZero R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddCq: argInt - ConstZero R: ReceiverResultReg]
  						ifFalse:
  							[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: Arg0Reg.
  							 self SubR: Arg0Reg R: ReceiverResultReg.
  							 jumpContinue := self JumpNoOverflow: 0.
  							 "overflow; must undo the damage before continuing"
  							 self AddR: Arg0Reg R: ReceiverResultReg.
  							 objectRepresentation genSetSmallIntegerTagsIn: Arg0Reg]].
  		[AndRR] -> [argIsInt
  						ifTrue: [instToAnnotate := self AndCq: argInt R: ReceiverResultReg]
  						ifFalse: [self AndR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0].
  		[OrRR]	-> [argIsInt
  						ifTrue: [instToAnnotate := self OrCq: argInt R: ReceiverResultReg]
  						ifFalse: [self OrR: Arg0Reg R: ReceiverResultReg].
  					jumpContinue := self Jump: 0] }.
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[annotateInst ifTrue: [self annotateBytecode: instToAnnotate].
  		 self MoveCq: argInt R: Arg0Reg].
  	self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1.
  	jumpContinue jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor nExts
  	  rcvrIsInt argIsInt rcvrInt argInt result jumpNotSmallInts inlineCAB annotateInst |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (rcvrInt := (self ssValue: 1) constant)].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[self cCode: '' inSmalltalk: "In Simulator ints are unsigned..."
  				[rcvrInt := objectMemory integerValueOf: rcvrInt.
  				argInt := objectMemory integerValueOf: argInt].
  		 primDescriptor opcode caseOf: {
  			[JumpLess]				-> [result := rcvrInt < argInt].
  			[JumpLessOrEqual]		-> [result := rcvrInt <= argInt].
  			[JumpGreater]			-> [result := rcvrInt > argInt].
  			[JumpGreaterOrEqual]	-> [result := rcvrInt >= argInt].
  			[JumpZero]				-> [result := rcvrInt = argInt].
  			[JumpNonZero]			-> [result := rcvrInt ~= argInt] }.
  		 "Must enter any annotatedConstants into the map"
+ 		 self annotateBytecodeIfAnnotated: (self ssValue: 1).
+ 		 self annotateBytecodeIfAnnotated: self ssTop.
- 		 (self ssValue: 1) annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
- 		 self ssTop annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
  		 "Must annotate the bytecode for correct pc mapping."
  		 self ssPop: 2.
  		 ^self ssPushAnnotatedConstant: (result
  											ifTrue: [objectMemory trueObject]
  											ifFalse: [objectMemory falseObject])].
  
  	nextPC := bytecodePC + primDescriptor numBytes.
  	nExts := 0.
  	[branchDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + (byte0 bitAnd: 256).
  	 branchDescriptor isExtension] whileTrue:
  		[nExts := nExts + 1.
  		 nextPC := nextPC + branchDescriptor numBytes].
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	targetBytecodePC := nextPC
  							+ branchDescriptor numBytes
  							+ (self spanFor: branchDescriptor at: nextPC exts: nExts in: methodObj).
  	postBranchPC := nextPC + branchDescriptor numBytes.
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
  	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	^self genMarshalledSend: (coInterpreter specialSelector: byte0 - self firstSpecialSelectorBytecodeOffset)
  		numArgs: 1!

Item was changed:
  ----- Method: TMethod>>superExpansionNodeFor:args: (in category 'inlining') -----
  superExpansionNodeFor: aSelector args: argumentNodes
  	"Answer the expansion of a super send.  Merge the super expansion's
  	 locals, properties and comment into this method's properties."
  	(definingClass superclass lookupSelector: aSelector)
  		ifNil: [self error: 'superclass does not define super method']
  		ifNotNil:
  			[:superMethod| | superTMethod commonVars varMap |
  			superTMethod := superMethod methodNode asTranslationMethodOfClass: self class.
  			((argumentNodes allSatisfy: [:parseNode| parseNode isVariableNode])
  			and: [(argumentNodes asOrderedCollection collect: [:parseNode| parseNode key]) = superTMethod args]) ifFalse:
  				[self error: definingClass name, '>>',selector, ' args ~= ',
  							superTMethod definingClass name, '>>', aSelector,
  							(String with: $. with: Character cr),
  							'For super expansions to be translated correctly each argument must be a variable with the same name as the corresponding argument in the super method.'].
  			self mergePropertiesOfSuperMethod: superTMethod.
+ 			(commonVars := superTMethod locals intersection: self locals) notEmpty ifTrue:
- 			(commonVars := superTMethod allLocals intersection: self allLocals) notEmpty ifTrue:
  				[varMap := Dictionary new.
  				 commonVars do:
  					[:k| varMap at: k put: (superTMethod unusedNamePrefixedBy: k avoiding: self allLocals)].
  				 superTMethod renameVariablesUsing: varMap].
+ 			self assert: (superTMethod locals allSatisfy: [:var| (self locals includes: var) not]).
- 			self assert: (superTMethod allLocals allSatisfy: [:var| (self allLocals includes: var) not]).
  			locals addAllFirst: superTMethod locals.
  			superTMethod declarations keysAndValuesDo:
  				[:var :decl|
  				self declarationAt: var put: decl].
  			superTMethod comment ifNotNil:
  				[:superComment|
  				comment := comment
  								ifNil: [superComment]
  								ifNotNil: [superComment, comment]].
  			superTMethod cascadeVariableNumber ifNotNil:
  				[:scvn|
  				cascadeVariableNumber := cascadeVariableNumber ifNil: [scvn] ifNotNil: [:cvn| cvn + scvn]].
  			superTMethod elideAnyFinalReturn.
  			^superTMethod parseTree]!

Item was changed:
  ----- Method: VMMaker>>generateEntire (in category 'generate sources') -----
  generateEntire
  	"Generate the interp, internal plugins and exports as well as the external plugins.
  	 If this comes from a generator, log it for convenience."
  	(thisContext findContextSuchThat: [:ctxt| ctxt selector == #generateConfiguration]) ifNotNil:
  		[:root|
  		(thisContext findContextSuchThat: [:ctxt| ctxt sender == root]) ifNotNil:
  			[:generator|
+ 			logger cr; nextPutAll: (generator selector copyReplaceAll: 'generate' with: '').
- 			logger nextPutAll: (generator selector copyReplaceAll: 'generate' with: '').
  			interpreterClassName ifNotNil: [logger space; nextPutAll: interpreterClassName].
  			logger cr; flush]].
  	self generateMainVM.
  	self generateExternalPlugins!



More information about the Vm-dev mailing list