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

commits at source.squeak.org commits at source.squeak.org
Sat Aug 9 01:12:28 UTC 2014


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

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

Name: VMMaker.oscog-eem.849
Author: eem
Time: 8 August 2014, 6:09:32.76 pm
UUID: 40f41a86-320e-4b77-b526-104a01f8adf0
Ancestors: VMMaker.oscog-eem.848

Convert Spur to use only the alternate CompiledMethod
header format (65536 literals, primitive in a bytecode).
3+4 evaluated in the simulator. 

Moved literal count methods from StackInterpreter
hierarchy to ObjectMemories.
Rename headerOf: to methodHeaderOf: &
literalCountOfHeader: to literalCountOfMethodHeader:
Abstract out lastPointerOfMethodHeader:

Cogits:
Fix offset of first special selector send not to presume
SqueakV3 and/or NewspeakV4.
Move guts of availableRegisterOrNi into the backEnd
allowing different ISAs to answer more registers.
Psrtially implement genCallPrimitiveBytecode.
Flesh out some of genBinaryVarOpVarInlinePrimitive: for
the Sista inline primitive code.  But the primitive numbers
still need reassigning.

Slang:
Collapse CoInterpreter and CoInterpreterMT's header
generation so interp.h is stable.

=============== Diff against VMMaker.oscog-eem.848 ===============

Item was changed:
  ----- Method: CoInterpreter class>>writeVMHeaderTo:bytesPerWord: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord
  	super writeVMHeaderTo: aStream bytesPerWord: bytesPerWord.
  	aStream
  		nextPutAll: '#define COGVM 1'; cr;
  		nextPutAll: '#if !!defined(COGMTVM)'; cr;
  		nextPutAll: '#	define COGMTVM 0'; cr;
+ 		nextPutAll: '#endif'; cr; cr.
+ 	"This constant is a hack for the MT VM on SqueakV3.  Eventually it will disappear.
+ 	 But having it here rather than in CoInterpreterMT means that the interp.h header
+ 	 doesn't  get regenerated every time the sources are, which means less recompilation."
+ 	((VMBasicConstants classPool associations select: [:a| a key beginsWith: 'DisownVM'])
+ 		asSortedCollection: [:a1 :a2| a1 value <= a2 value])
+ 		do: [:a|
+ 			aStream nextPutAll: '#define '; nextPutAll: a key; space; print: a value; cr]!
- 		nextPutAll: '#endif'; cr!

Item was changed:
  ----- Method: CoInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode inInterpreter switched |
  
+ 	methodHeader := objectMemory methodHeaderOf: newMethod.
- 	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 assert: (objectMemory isOopForwarded: rcvr) 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: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	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:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	"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>>checkOkayFields: (in category 'debug support') -----
  checkOkayFields: oop
  	"Check if the argument is an ok object.
  	 If this is a pointers object, check that its fields are all okay oops."
  
  	| hasYoung i fieldOop |
  	(oop = nil or: [oop = 0]) ifTrue: [ ^true ]. "?? eem 1/16/2013"
  	(objectMemory isIntegerObject: oop) ifTrue: [ ^true ].
  	(objectMemory checkOkayOop: oop) ifFalse: [ ^false ].
  	(objectMemory checkOopHasOkayClass: oop) ifFalse: [ ^false ].
  	((objectMemory isPointersNonImm: oop) or: [objectMemory isCompiledMethod: oop]) ifFalse: [ ^true ].
  	hasYoung := objectMemory hasSpurMemoryManagerAPI not
  				  and: [objectMemory isYoungObject: (objectMemory fetchClassOfNonImm: oop)].
  	(objectMemory isCompiledMethod: oop)
  		ifTrue:
+ 			[i := (objectMemory literalCountOf: oop) + LiteralStart - 1]
- 			[i := (self literalCountOf: oop) + LiteralStart - 1]
  		ifFalse:
  			[(objectMemory isContext: oop)
  				ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
  				ifFalse: [i := (objectMemory lengthOf: oop) - 1]].
  	[i >= 0] whileTrue:
  		[fieldOop := objectMemory fetchPointer: i ofObject: oop.
  		(objectMemory isNonIntegerObject: fieldOop) ifTrue:
  			[(i = 0 and: [objectMemory isCompiledMethod: oop])
  				ifTrue:
  					[(cogMethodZone methodFor: (self pointerForOop: fieldOop)) = 0 ifTrue:
  						[self print: 'method '; printHex: oop; print: ' has an invalid cog method reference'.
  						^false]]
  				ifFalse:
  					[hasYoung := hasYoung or: [objectMemory isYoung: fieldOop].
  					(objectMemory checkOkayOop: fieldOop) ifFalse: [ ^false ].
  					(self checkOopHasOkayClass: fieldOop) ifFalse: [ ^false ]]].
  		i := i - 1].
  	hasYoung ifTrue:
  		[^objectMemory checkOkayYoungReferrer: oop].
  	^true!

Item was changed:
  ----- Method: CoInterpreter>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
  	<var: #cogHomeMethod type: #'CogHomeMethod *'>
  	<returnTypeC: #usqInt>
  	"Convert the current interpreter frame into a machine code frame
  	 and answer the machine code pc matching bcpc."
  	| startBcpc methodField closure cogMethod pc |
  	<var: #cogMethod type: #'CogBlockMethod *'>
  	<var: #p type: #'char *'>
  	self assert: (self isMachineCodeFrame: framePointer) not.
  	"Update the return pc, perhaps saving it in the caller's iframeSavedIP."
  	(self isBaseFrame: framePointer)
  		ifTrue:
  			[stackPages
  				longAt: framePointer + FoxCallerSavedIP
  				put: cogit ceBaseFrameReturnPC]
  		ifFalse:
  			[(self isMachineCodeFrame: (self frameCallerFP: framePointer)) ifFalse:
  				[self iframeSavedIP: (self frameCallerFP: framePointer)
  					put: (self frameCallerSavedIP: framePointer) asInteger.
  				 stackPages
  					longAt: framePointer + FoxCallerSavedIP
  					put: cogit ceReturnToInterpreterPC]].
  	"Compute the cog method field"
  	(self iframeIsBlockActivation: framePointer)
  		ifTrue:
  			[closure := self pushedReceiverOrClosureOfFrame: framePointer.
  			 startBcpc := self startPCOfClosure: closure.
  			 cogMethod := cogit
  								findMethodForStartBcpc: startBcpc
  								inHomeMethod: cogHomeMethod.
  			 methodField := cogMethod asInteger + MFMethodFlagIsBlockFlag]
  		ifFalse:
  			[startBcpc := self startPCOfMethodHeader: cogHomeMethod methodHeader.
  			 cogMethod := self cCoerceSimple: cogHomeMethod to: #'CogBlockMethod *'.
  			 methodField := cogHomeMethod asInteger].
  	"compute the pc before converting the frame to help with debugging."
  	pc := cogit mcPCForBackwardBranch: bcpc startBcpc: startBcpc in: cogMethod.
  	self assert: pc > (cogMethod asUnsignedInteger + cogit noCheckEntryOffset).
+ 	self assert: bcpc = (cogit bytecodePCFor: pc startBcpc: startBcpc in: cogMethod).
- 	self assert: bcpc = (self bytecodePCFor: pc startBcpc: startBcpc in: cogMethod).
  	"now convert to a machine code frame"
  	stackPages
  		longAt: framePointer + FoxMethod
  		put: methodField
  			+ ((self iframeHasContext: framePointer)
  				ifTrue: [MFMethodFlagHasContextFlag]
  				ifFalse: [0]).
  	framePointer + FoxIFReceiver to: stackPointer by: BytesPerWord negated do:
  		[:p|
  		stackPages longAt: p + FoxMFReceiver - FoxIFReceiver put: (stackPages longAt: p)].
  	stackPointer := stackPointer + FoxMFReceiver - FoxIFReceiver.
  	^pc!

Item was changed:
  ----- Method: CoInterpreter>>functionForPrimitiveExternalCall: (in category 'plugin primitives') -----
  functionForPrimitiveExternalCall: methodObj
  	"Arrange to call the external primitive directly.  The complication is arranging
  	 that the call can be flushed, given that it is embedded in machine code."
  	<returnTypeC: 'void (*functionForPrimitiveExternalCall(sqInt methodObj))(void)'>
  	| lit index functionPointer |
  	<var: #functionPointer declareC: #'void (*functionPointer)(void)'>
  	cogit setPostCompileHook: #recordCallOffsetIn:of:.
+ 	(objectMemory literalCountOf: methodObj) > 0 ifFalse:
- 	(self literalCountOf: methodObj) > 0 ifFalse:
  		[^#primitiveExternalCall].
  	lit := self literal: 0 ofMethod: methodObj. 
  	"Check if it's an array of length 4"
  	((objectMemory isArray: lit) and: [(objectMemory lengthOf: lit) = 4]) ifFalse:
  		[^#primitiveExternalCall].
  	index := objectMemory fetchPointer: 3 ofObject: lit.
  	((objectMemory isIntegerObject: index)
  	and: [(index := objectMemory integerValueOf: index) > 0
  	and: [index <= MaxExternalPrimitiveTableSize]]) ifFalse:
  		[^#primitiveExternalCall].
  	functionPointer := externalPrimitiveTable at: index - 1.
  	functionPointer = 0 ifTrue:
  		[^#primitiveExternalCall].
  	^functionPointer!

Item was removed:
- ----- Method: CoInterpreter>>headerOf: (in category 'compiled methods') -----
- headerOf: methodPointer
- 	<api>
- 	| methodHeader |
- 	methodHeader := self rawHeaderOf: methodPointer.
- 	^(self isCogMethodReference: methodHeader)
- 		ifTrue:
- 			[self assert: (self cCoerceSimple: methodHeader to: #'CogMethod *') objectHeader = objectMemory nullHeaderForMachineCodeMethod.
- 			(self cCoerceSimple: methodHeader to: #'CogMethod *') methodHeader]
- 		ifFalse: [methodHeader]!

Item was changed:
  ----- Method: CoInterpreter>>ifBackwardsCheckForEvents: (in category 'jump bytecodes') -----
  ifBackwardsCheckForEvents: offset
  	"Backward jump means we're in a loop.
  		- check for possible interrupts.
  		- check for long-running loops and JIT if appropriate."
  	| switched backwardJumpCountByte |
  	<inline: true>
  	offset >= 0 ifTrue:
  		[^self].
  
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 switched := self checkForEventsMayContextSwitch: true.
  		 self returnToExecutive: true postContextSwitch: switched.
  		 self browserPluginReturnIfNeeded.
  		 self internalizeIPandSP.
  		 switched ifTrue:
  			[^self]].
  
  	"We use the least significant byte of the flags word (which is marked as an immediate) and
  	 subtract two each time to avoid disturbing the least significant tag bit.  Since the byte is
  	 initialized to 1 (on frame build), on first decrement it will become -1.  Trip when it reaches 1 again."
  	backwardJumpCountByte := self iframeBackwardBranchByte: localFP.
  	(backwardJumpCountByte := backwardJumpCountByte - 2) = 1
  		ifTrue:
+ 			[(self methodWithHeaderShouldBeCogged: (objectMemory methodHeaderOf: method)) ifTrue:
- 			[(self methodWithHeaderShouldBeCogged: (self headerOf: method)) ifTrue:
  				[self externalizeIPandSP.
  				 self attemptToSwitchToMachineCode: (self oopForPointer: localIP) - offset - method - BaseHeaderSize - 1
  				 "If attemptToSwitchToMachineCode: returns the method could not be cogged, hence..."].
  			 "can't cog method; avoid asking to cog it again for the longest possible time."
  			 backwardJumpCountByte := 16r7F]
  		ifFalse:
  			[backwardJumpCountByte = -1 ifTrue: "initialize the count"
  				[self assert: minBackwardJumpCountForCompile <= 128.
  				 backwardJumpCountByte := minBackwardJumpCountForCompile - 1 << 1 + 1]].
  	self iframeBackwardBranchByte: localFP put: backwardJumpCountByte!

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 rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	<var: #cogMethod type: #'CogMethod *'>
  	"theIP must be typed as signed because it is assigned ceCannotResumePC and so maybe implicitly typed as unsigned."
  	<var: #theIP type: #sqInt>
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	self assert: HasBeenReturnedFromMCPC signedIntFromLong < 0.
  	theIP := (objectMemory isIntegerObject: theIP)
  				ifTrue: [objectMemory integerValueOf: theIP]
  				ifFalse: [HasBeenReturnedFromMCPC].
  	theMethod := objectMemory followObjField: 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.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: 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 nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: maybeClosure]
  		ifFalse:
  			[| header |
+ 			 header := objectMemory methodHeaderOf: theMethod.
- 			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
+ 			 "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)].
- 			 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)]].
  			 stackPages
  				longAt: (pointer := pointer - BytesPerWord)
  				put: rcvr].
  	"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
  			  the native pc anyway we should create a native method and native frame."
  			 cogMethod := self ensureMethodIsCogged: theMethod.
  			 theMethod := cogMethod 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 blockAlignment).
  							 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: rcvr.
  	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.
  	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 validStackPageBaseFrame: page).
  	^page!

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

Item was changed:
  ----- Method: CoInterpreter>>methodNeedsLargeContext: (in category 'cog jit support') -----
  methodNeedsLargeContext: methodObj
  	<api>
+ 	^self methodHeaderIndicatesLargeFrame: (objectMemory methodHeaderOf: methodObj)!
- 	^(self headerOf: methodObj) anyMask: LargeContextBit!

Item was changed:
  ----- Method: CoInterpreter>>methodShouldBeCogged: (in category 'compiled methods') -----
  methodShouldBeCogged: aMethodObj
  	<api>
+ 	(self methodWithHeaderShouldBeCogged: (objectMemory methodHeaderOf: aMethodObj)) ifTrue:
- 	(self methodWithHeaderShouldBeCogged: (self headerOf: aMethodObj)) ifTrue:
  		[^true].
  	self maybeFlagMethodAsInterpreted: aMethodObj.
  	^false!

Item was changed:
  ----- Method: CoInterpreter>>methodWithHeaderShouldBeCogged: (in category 'compiled methods') -----
  methodWithHeaderShouldBeCogged: methodHeader
  	"At the moment jit any method with less than N literals, where N defaults to 60.
  	 See e.g. SimpleStackBasedCogit class>>initialize.
  	 In my dev image eem 2/22/2009 13:39
  		(30 to: 100 by: 5) collect:
  			[:n| n -> (SystemNavigation default allSelect: [:m| m numLiterals > n]) size]
  		#(30->1681 35->1150 40->765 45->523 50->389 55->289 60->206
  		    65->151 70->124 75->99 80->73 85->63 90->54 95->42 100->38).
  	 And running the CogVMSimulator with flagging of interpreted methods turned on reveals
  	 the following sizes of interpreted methods.
  		| sizes |
  		sizes := Bag new.
  		SystemNavigation default allSelect: [:m| m flag ifTrue: [sizes add: m numLiterals]. false].
  		sizes sortedElements asArray
  			#(	40->4 41->1 42->2 44->1 45->3 46->1 47->2 48->1
  				50->2 51->1 53->1 55->1 56->1
  				87->1 108->1 171->1)
  	 literalCountOfHeader: does not include the header word."
+ 	^(objectMemory literalCountOfMethodHeader: methodHeader) <= maxLiteralCountForCompile!
- 	^(self literalCountOfHeader: methodHeader) <= maxLiteralCountForCompile!

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 |
  	<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 assert: bcpc >= (self startPCOfMethod: methodObj).
+ 	"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)].
- 	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>>roomToPushNArgs: (in category 'primitive support') -----
  roomToPushNArgs: n
  	"Answer if there is room to push n arguments onto the current stack.  We assume
  	 this is called by primitives that check there is enough room in any new context, and
  	 won't actually push the arguments in the current context if the primitive fails.  With
  	 this assumption it is safe to answer based on the maximum argument count, /not/
  	 the ammount of space in the current frame were it converted to a context.."
  	false
  		ifTrue: "old code that checked size of context..."
  			[| methodHeader cntxSize |
  			(self isMachineCodeFrame: framePointer)
  				ifTrue: [methodHeader := (self mframeHomeMethod: framePointer) methodHeader]
+ 				ifFalse: [methodHeader := objectMemory methodHeaderOf: (self iframeMethod: framePointer)].
+ 			cntxSize := (self methodHeaderIndicatesLargeFrame: methodHeader)
- 				ifFalse: [methodHeader := self headerOf: (self iframeMethod: framePointer)].
- 			cntxSize := (methodHeader bitAnd: LargeContextBit) ~= 0
  							ifTrue: [LargeContextSlots - CtxtTempFrameStart]
  							ifFalse: [SmallContextSlots - CtxtTempFrameStart].
  			^self stackPointerIndex + n <= cntxSize]
  		ifFalse: "simpler code that simply insists args are <= max arg count"
  			[^n <= (LargeContextSlots - CtxtTempFrameStart)]!

Item was changed:
  ----- Method: CoInterpreter>>startPCOfMethodHeader: (in category 'compiled methods') -----
  startPCOfMethodHeader: aCompiledMethodHeader
  	<api>
  	"Zero-relative version of CompiledMethod>>startpc."
+ 	^(objectMemory literalCountOfMethodHeader: aCompiledMethodHeader) + LiteralStart * objectMemory bytesPerOop!
- 	^(self literalCountOfHeader: aCompiledMethodHeader) + LiteralStart * objectMemory bytesPerOop!

Item was removed:
- ----- Method: CoInterpreterMT class>>writeVMHeaderTo:bytesPerWord: (in category 'translation') -----
- writeVMHeaderTo: aStream bytesPerWord: bytesPerWord
- 	super writeVMHeaderTo: aStream bytesPerWord: bytesPerWord.
- 	aStream cr.
- 	((VMBasicConstants classPool associations select: [:a| a key beginsWith: 'DisownVM'])
- 		asSortedCollection: [:a1 :a2| a1 value <= a2 value])
- 		do: [:a|
- 			aStream nextPutAll: '#define '; nextPutAll: a key; space; print: a value; cr]!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
  	| current index next stackSize stackp freeStartAtStart |
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
  	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
  						[next := (objectMemory isContextNonImm: current)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: (self cCoerceSimple: next to: #'char *')
  										onPage: (stackPages stackPageFor: (self cCoerceSimple: next to: #'char *')))]
  			ifFalse:
  				[next >= heapBase ifTrue: "exclude Cog methods"
  					[self assert: (self checkOkayOop: next)]].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[next >= heapBase "exclude Cog methods"
  					  and: [(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
  						[objectMemory mark: next.
  						 (objectMemory isCompiledMethod: next)
+ 							ifTrue: [index := (objectMemory literalCountOf: next) + LiteralStart]
- 							ifTrue: [index := (self literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveObjectAt (in category 'object access primitives') -----
  primitiveObjectAt
  "Defined for CompiledMethods only"
  	| thisReceiver rawHeader realHeader index |
  	index  := self stackIntegerValue: 0.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	thisReceiver := self stackValue: 1.
  	rawHeader := self rawHeaderOf: thisReceiver.
  	realHeader := (self isCogMethodReference: rawHeader)
  					ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]
  					ifFalse: [rawHeader].
  	(index > 0
+ 	 and: [index <= ((objectMemory literalCountOfMethodHeader: realHeader) + LiteralStart)]) ifFalse:
- 	 and: [index <= ((self literalCountOfHeader: realHeader) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	self pop: 2
  		thenPush: (index = 1
  					ifTrue: [realHeader]
  					ifFalse: [objectMemory fetchPointer: index - 1 ofObject: thisReceiver])!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
  	"Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
  	| thisReceiver rawHeader realHeader index newValue |
  	newValue := self stackValue: 0.
  	index := self stackValue: 1.
  	(objectMemory isNonIntegerObject: index) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	thisReceiver := self stackValue: 2.
  	rawHeader := self rawHeaderOf: thisReceiver.
  	realHeader := (self isCogMethodReference: rawHeader)
  					ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader]
  					ifFalse: [rawHeader].
  	(index > 0
+ 	 and: [index <= ((objectMemory literalCountOfMethodHeader: realHeader) + LiteralStart)]) ifFalse:
- 	 and: [index <= ((self literalCountOfHeader: realHeader) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	index = 1
  		ifTrue:
  			[((objectMemory isNonIntegerObject: newValue)
+ 			 or: [(objectMemory literalCountOfMethodHeader: newValue) ~= (objectMemory literalCountOfMethodHeader: realHeader)]) ifTrue:
- 			 or: [(self literalCountOfHeader: newValue) ~= (self literalCountOfHeader: realHeader)]) ifTrue:
  				[^self primitiveFailFor: PrimErrBadArgument].
  			 (self isCogMethodReference: rawHeader)
  				ifTrue: [(self cCoerceSimple: rawHeader to: #'CogMethod *') methodHeader: newValue]
  				ifFalse: [objectMemory storePointerUnchecked: 0 ofObject: thisReceiver withValue: newValue]]
  		ifFalse:
  			[objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue].
  	self pop: 3 thenPush: newValue!

Item was added:
+ ----- Method: CogAbstractInstruction>>availableRegisterOrNilFor: (in category 'register allocation') -----
+ availableRegisterOrNilFor: liveRegsMask
+ 	"Answer an unused abstract register in the liveRegMask.
+ 	 Subclasses with more registers can override to answer them."
+ 	<returnTypeC: #sqInt>
+ 	(liveRegsMask anyMask: (cogit registerMaskFor: Arg1Reg)) ifFalse:
+ 		[^Arg1Reg].
+ 	(liveRegsMask anyMask: (cogit registerMaskFor: Arg0Reg)) ifFalse:
+ 		[^Arg0Reg].
+ 	(liveRegsMask anyMask: (cogit registerMaskFor: SendNumArgsReg)) ifFalse:
+ 		[^SendNumArgsReg].
+ 	(liveRegsMask anyMask: (cogit registerMaskFor: ClassReg)) ifFalse:
+ 		[^ClassReg].
+ 	(liveRegsMask anyMask: (cogit registerMaskFor: ReceiverResultReg)) ifFalse:
+ 		[^ReceiverResultReg].
+ 	^nil!

Item was changed:
  ----- Method: CogVMSimulator>>convertToMachineCodeFrame:bcpc: (in category 'frame access') -----
  convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc
+ 	"bytecodeSetSelector ~= 0 ifTrue: [self halt]".
- 	"bytecodeSetSelector ~= 0 ifTrue: ["self halt"]".
  	^super convertToMachineCodeFrame: cogHomeMethod bcpc: bcpc!

Item was changed:
  CogClass subclass: #Cogit
  	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent primitiveIndex backEnd callerSavedRegMask postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall interpretLabel endCPICCase0 endCPICCase1 numPICCases firstCPICCaseOffset cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes annotations generatorTable primitiveGeneratorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes annotationIndex blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB numIRCs indexOfIRC theIRCs'
+ 	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation FirstSpecialSelector HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumOopsPerIRC NumSendTrampolines NumTrampolines ProcessorClass ShouldNotJIT UnimplementedPrimitive YoungSelectorInPIC'
- 	classVariableNames: 'AltBlockCreationBytecodeSize AltNSSendIsPCAnnotated AnnotationConstantNames AnnotationShift BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration EncounteredUnknownBytecode FirstAnnotation HasBytecodePC InsufficientCodeSpace IsAbsPCReference IsDisplacement IsDisplacementX2N IsNSSendCall IsObjectReference IsRelativeCall IsSendCall MapEnd MaxCompiledPrimitiveIndex MaxNegativeErrorCode MaxStackAllocSize MaxUnitDisplacement MaxX2NDisplacement MethodTooBig NSSendIsPCAnnotated NotFullyInitialized NumObjRefsInRuntime NumOopsPerIRC NumSendTrampolines NumTrampolines ProcessorClass ShouldNotJIT UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
  !Cogit commentStamp: 'eem 2/13/2013 15:37' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	StackToRegisterMappingCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
  cFramePointer cStackPointer <Integer>
  	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixup shas one element per byte in methodObj's bytecode
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventuakly teh total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid"
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV3PlusClosuresNewspeakV4Hybrid"
  
  	| v3Table v4Table |
+ 	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize et al correctly."
- 	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize correctly."
  	self initializeBytecodeTableForNewspeakV4.
  	v4Table := generatorTable.
  	AltBlockCreationBytecodeSize := BlockCreationBytecodeSize.
  	AltNSSendIsPCAnnotated := NSSendIsPCAnnotated.
+ 	AltFirstSpecialSelector := FirstSpecialSelector.
  	self initializeBytecodeTableForNewspeakV3PlusClosures.
  	v3Table := generatorTable.
  	generatorTable := CArrayAccessor on: v3Table object, v4Table object!

Item was changed:
  ----- Method: Cogit class>>initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid"
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid"
  
  	| v3Table v1Table |
+ 	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize et al correctly."
- 	"N.B. Must do it backwards to evaluate AltBlockCreationBytecodeSize & BlockCreationBytecodeSize correctly."
  	self initializeBytecodeTableForSistaV1.
  	v1Table := generatorTable.
  	AltBlockCreationBytecodeSize := BlockCreationBytecodeSize.
+ 	AltFirstSpecialSelector := FirstSpecialSelector.
  	self initializeBytecodeTableForSqueakV3PlusClosures.
  	v3Table := generatorTable.
  	generatorTable := CArrayAccessor on: v3Table object, v1Table object!

Item was changed:
  ----- Method: Cogit>>addCleanBlockStarts (in category 'compile abstract instructions') -----
  addCleanBlockStarts
+ 	1 to: (objectMemory literalCountOf: methodObj) do:
- 	1 to: (coInterpreter literalCountOf: methodObj) do:
  		[:i| | lit |
  		lit := coInterpreter fetchPointer: i ofObject: methodObj.
  		(coInterpreter startPCOrNilOfLiteral: lit in: methodObj) ifNotNil:
  			[:startPCOrNil|
  			 maxLitIndex := maxLitIndex max: i.
  			 self addBlockStartAt: startPCOrNil - 1 "1-rel => 0-rel"
  				numArgs: (coInterpreter argumentCountOfClosure: lit)
  				numCopied: (coInterpreter copiedValueCountOfClosure: lit)
  				span: (self spanForCleanBlockStartingAt: startPCOrNil - 1)]]!

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

Item was changed:
  ----- Method: Cogit>>lastBytecodePCForBlockAt:in: (in category 'method map') -----
  lastBytecodePCForBlockAt: startbcpc in: aMethodObj
  	"Answer the 0-relative pc of the last bytecode in the block starting at the 0-relative startbcpc in aMethodObj."
  	| methodHeader bcpc bsOffset byte descriptor |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	methodHeader := objectMemory methodHeaderOf: aMethodObj.
- 	methodHeader := coInterpreter headerOf: aMethodObj.
  	bcpc := startbcpc - (self blockCreationBytecodeSizeForHeader: methodHeader).
  	bsOffset := self bytecodeSetOffsetForHeader: methodHeader.
  	byte := (objectMemory fetchByte: bcpc ofObject: aMethodObj) + bsOffset.
  	descriptor := self generatorAt: byte.
  	^(self nextBytecodePCFor: descriptor at: bcpc exts: -1 in: aMethodObj) - 1!

Item was changed:
  ----- Method: Cogit>>method:hasSameCodeAs: (in category 'garbage collection') -----
  method: methodA hasSameCodeAs: methodB
  	"For the purposes of become: see if the two methods are similar, i.e. can be safely becommed.
  	 This is pretty strict.  All literals and bytecodes must be identical.  Only trailer bytes and header
  	  flags can differ."
  	<inline: false>
  	| headerA headerB numLitsA endPCA |
+ 	headerA := objectMemory methodHeaderOf: methodA.
+ 	headerB := objectMemory methodHeaderOf: methodB.
+ 	numLitsA := objectMemory literalCountOfMethodHeader: headerA.
- 	headerA := coInterpreter headerOf: methodA.
- 	headerB := coInterpreter headerOf: methodB.
- 	numLitsA := coInterpreter literalCountOfHeader: headerA.
  	endPCA := self endPCOf: methodA.
  	((coInterpreter argumentCountOfMethodHeader: headerA) ~= (coInterpreter argumentCountOfMethodHeader: headerB)
  	 or: [(coInterpreter temporaryCountOfMethodHeader: headerA) ~= (coInterpreter temporaryCountOfMethodHeader: headerB)
  	 or: [(coInterpreter primitiveIndexOfMethod: methodA header: headerA) ~= (coInterpreter primitiveIndexOfMethod: methodB header: headerB)
+ 	 or: [numLitsA ~= (objectMemory literalCountOfMethodHeader: headerB)
- 	 or: [numLitsA ~= (coInterpreter literalCountOfHeader: headerB)
  	 or: [endPCA > (objectMemory numBytesOf: methodB)]]]]) ifTrue:
  		[^false].
  	 1 to: numLitsA - 1 do:
  		[:li|
  		(objectMemory fetchPointer: li ofObject: methodA) ~= (objectMemory fetchPointer: li ofObject: methodB) ifTrue:
  			[^false]].
  	(coInterpreter startPCOfMethod: methodA) to: endPCA do:
  		[:bi|
  		(objectMemory fetchByte: bi ofObject: methodA) ~= (objectMemory fetchByte: bi ofObject: methodB) ifTrue:
  			[^false]].
  	^true!

Item was changed:
  ----- Method: Cogit>>method:hasSameCodeAs:checkPenultimate: (in category 'garbage collection') -----
  method: methodA hasSameCodeAs: methodB checkPenultimate: comparePenultimateLiteral
  	"For the purposes of become: see if the two methods are similar, i.e. can be safely becommed.
  	 This is pretty strict.  All literals and bytecodes must be identical.  Only trailer bytes and header
  	  flags can differ."
  	<inline: false>
  	| headerA headerB numLitsA endPCA |
+ 	headerA := objectMemory methodHeaderOf: methodA.
+ 	headerB := objectMemory methodHeaderOf: methodB.
+ 	numLitsA := objectMemory literalCountOfMethodHeader: headerA.
- 	headerA := coInterpreter headerOf: methodA.
- 	headerB := coInterpreter headerOf: methodB.
- 	numLitsA := coInterpreter literalCountOfHeader: headerA.
  	endPCA := self endPCOf: methodA.
  	((coInterpreter argumentCountOfMethodHeader: headerA) ~= (coInterpreter argumentCountOfMethodHeader: headerB)
  	 or: [(coInterpreter temporaryCountOfMethodHeader: headerA) ~= (coInterpreter temporaryCountOfMethodHeader: headerB)
  	 or: [(coInterpreter primitiveIndexOfMethod: methodA header: headerA) ~= (coInterpreter primitiveIndexOfMethod: methodB header: headerB)
+ 	 or: [numLitsA ~= (objectMemory literalCountOfMethodHeader: headerB)
- 	 or: [numLitsA ~= (coInterpreter literalCountOfHeader: headerB)
  	 or: [endPCA > (objectMemory numBytesOf: methodB)]]]]) ifTrue:
  		[^false].
  	 1 to: numLitsA - 1 do:
  		[:li|
  		(objectMemory fetchPointer: li ofObject: methodA) ~= (objectMemory fetchPointer: li ofObject: methodB) ifTrue:
  			[(li < (numLitsA - 1) "If the method doesn't use the penultimate literal then don't fail the comparison."
  			  or: [comparePenultimateLiteral]) ifTrue:
  				[^false]]].
  	(coInterpreter startPCOfMethod: methodA) to: endPCA do:
  		[:bi|
  		(objectMemory fetchByte: bi ofObject: methodA) ~= (objectMemory fetchByte: bi ofObject: methodB) ifTrue:
  			[^false]].
  	^true!

Item was changed:
  ----- Method: Cogit>>noAssertMethodClassAssociationOf: (in category 'debugging') -----
  noAssertMethodClassAssociationOf: methodPointer
  	^coInterpreter
+ 		literal: (objectMemory literalCountOfMethodHeader: (coInterpreter noAssertHeaderOf: methodPointer)) - 1
- 		literal: (coInterpreter literalCountOfHeader: (coInterpreter noAssertHeaderOf: methodPointer)) - 1
  		ofMethod: methodPointer!

Item was changed:
  ----- Method: Cogit>>scanForCleanBlocks (in category 'compile abstract instructions') -----
  scanForCleanBlocks
  	"Answer the number of clean blocks found in the literal frame"
  	| numCleanBlocks |
  	numCleanBlocks := 0.
+ 	1 to: (objectMemory literalCountOf: methodObj) do:
- 	1 to: (coInterpreter literalCountOf: methodObj) do:
  		[:i| | lit |
+ 		lit := objectMemory fetchPointer: i ofObject: methodObj.
- 		lit := coInterpreter fetchPointer: i ofObject: methodObj.
  		(coInterpreter startPCOrNilOfLiteral: lit in: methodObj) ifNotNil:
  			[:startPCOrNil| numCleanBlocks := numCleanBlocks + 1]].
  	^numCleanBlocks!

Item was changed:
  ----- Method: Cogit>>traceMap:byte:at:for: (in category 'method map') -----
  traceMap: annotation byte: byte at: address for: mcpc
  	<cmacro: '(ig,no,re,d) 0'>
  	| s code bytecode |
  	(compilationTrace anyMask: 16) ifTrue:
  		[code := annotation isInteger ifTrue: [annotation] ifFalse: [annotation annotation].
  		(s := coInterpreter transcript)
  			ensureCr;
  			print: code; nextPut: $/; nextPutAll: byte hex; space;
  			nextPutAll: address hex; space; nextPutAll: mcpc hex; space;
  			nextPutAll: (AnnotationConstantNames detect: [:name| (Cogit classPool at: name ifAbsent: []) = code]); cr; flush.
  		(annotation isInteger not
  		 and: [annotation instruction bcpc isInteger]) ifTrue:
  			[s tab; print: annotation instruction bcpc; nextPut: $/.
  			 annotation instruction bcpc printOn: s base: 16.
  			 s space.
  			 annotation instruction printStateOn: s.
  			 s space.
  			 bytecode := objectMemory fetchByte: annotation instruction bcpc ofObject: methodObj.
+ 			 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (objectMemory methodHeaderOf: methodObj)).
- 			 bytecode := bytecode + (self bytecodeSetOffsetForHeader: (coInterpreter headerOf: methodObj)).
  			 (self generatorAt: bytecode) printStateOn: s.
  			 s cr; flush]]!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>headerOf: (in category 'accessing') -----
- headerOf: aMethodOop
- 	^self rawHeaderOf: aMethodOop!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>literalCountOfHeader: (in category 'accessing') -----
- literalCountOfHeader: methodHeader
- 	^(headerToMethodMap at: methodHeader) numLiterals!

Item was changed:
  ----- Method: Interpreter>>activateNewClosureMethod: (in category 'control primitives') -----
  activateNewClosureMethod: blockClosure
  	"Similar to activateNewMethod but for Closure and newMethod."
  	| theBlockClosure closureMethod newContext methodHeader numCopied where outerContext |
  
  	DoAssertionChecks ifTrue:
  		[self okayOop: blockClosure].
  	outerContext := self fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	DoAssertionChecks ifTrue:
  		[self okayOop: outerContext].
  	closureMethod := self fetchPointer: MethodIndex ofObject: outerContext.
+ 	methodHeader := self methodHeaderOf: closureMethod.
- 	methodHeader := self headerOf: closureMethod.
  	self pushRemappableOop: blockClosure.
  	newContext := self allocateOrRecycleContext: (methodHeader bitAnd: LargeContextBit). "All for one, and one for all!!"
  
  	"allocateOrRecycleContext: may cause a GC; restore blockClosure and refetch outerContext et al"
  	theBlockClosure := self popRemappableOop.
  	outerContext := self fetchPointer: ClosureOuterContextIndex ofObject: theBlockClosure.
  	numCopied := (self numSlotsOf: theBlockClosure) - ClosureFirstCopiedValueIndex.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where :=  newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord)
  		put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord)
  		put: (self fetchPointer: ClosureStartPCIndex ofObject: theBlockClosure).
  	self longAt: where + (StackPointerIndex << ShiftForWord)
  		put: (self integerObjectOf: argumentCount + numCopied).
  	self longAt: where + (MethodIndex << ShiftForWord)
  		put: (self fetchPointer: MethodIndex ofObject: outerContext).
  	self longAt: where + (ClosureIndex << ShiftForWord)
  		put: theBlockClosure.
  	self longAt: where + (ReceiverIndex << ShiftForWord)
  		put: (self fetchPointer: ReceiverIndex ofObject: outerContext).
  
  	"Copy the arguments..."
  	1 to: argumentCount do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord)
  				put: (self stackValue: argumentCount-i)].
  
  	"Copy the copied values..."
  	where := newContext + BaseHeaderSize + ((ReceiverIndex + 1 + argumentCount) << ShiftForWord).
  	0 to: numCopied - 1 do:
  		[:i| self longAt: where + (i << ShiftForWord)
  				put: (self fetchPointer: i + ClosureFirstCopiedValueIndex
  						  ofObject: theBlockClosure)].
  
  	"The initial instructions in the block nil-out remaining temps."
  
  	self pop: argumentCount + 1.
  	self newActiveContext: newContext!

Item was changed:
  ----- Method: Interpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| newContext methodHeader initialIP tempCount nilOop where |
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	newContext := self allocateOrRecycleContext: (methodHeader bitAnd: LargeContextBit).
  
+ 	initialIP := ((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1.
- 	initialIP := ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1.
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  
  	where :=  newContext  + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord) put: (self integerObjectOf: initialIP).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  	self longAt: where + (ClosureIndex << ShiftForWord) put: nilObj.
  
  	"Copy the receiver and arguments..."
  	0 to: argumentCount do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord) put: (self stackValue: argumentCount-i)].
  
  	"clear remaining temps to nil in case it has been recycled"
  	nilOop := nilObj.
  	argumentCount+1+ReceiverIndex to: tempCount+ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: nilOop].
  
  	self pop: argumentCount + 1.
  	reclaimableContextCount := reclaimableContextCount + 1.
  	self newActiveContext: newContext.!

Item was changed:
  ----- Method: Interpreter>>argumentCountOf: (in category 'compiled methods') -----
  argumentCountOf: methodPointer
+ 	^((self methodHeaderOf: methodPointer) >> 25) bitAnd: 16r0F!
- 	^ ((self headerOf: methodPointer) >> 25) bitAnd: 16r0F!

Item was removed:
- ----- Method: Interpreter>>headerOf: (in category 'compiled methods') -----
- headerOf: methodPointer
- 	^self fetchPointer: HeaderIndex ofObject: methodPointer!

Item was changed:
  ----- Method: Interpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader newContext tempCount argCount2 needsLarge where |
  	<inline: true>
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	needsLarge := methodHeader bitAnd: LargeContextBit.
  	(needsLarge = 0 and: [freeContexts ~= NilContext])
  		ifTrue: [newContext := freeContexts.
  				freeContexts := self fetchPointer: 0 ofObject: newContext]
  		ifFalse: ["Slower call for large contexts or empty free list"
  				self externalizeIPandSP.
  				newContext := self allocateOrRecycleContext: needsLarge.
  				self internalizeIPandSP].
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where :=   newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord)
+ 		put: (self integerObjectOf: (((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1)).
- 		put: (self integerObjectOf: (((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1)).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  	self longAt: where + (ClosureIndex << ShiftForWord) put: nilObj.
  
  	"Copy the receiver and arguments..."
  	argCount2 := argumentCount.
  	0 to: argCount2 do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord) put: (self internalStackValue: argCount2-i)].
  
  	"clear remaining temps to nil in case it has been recycled"
  	methodHeader := nilObj.  "methodHeader here used just as faster (register?) temp"
  	argCount2+1+ReceiverIndex to: tempCount+ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: methodHeader].
  
  	self internalPop: argCount2 + 1.
  	reclaimableContextCount := reclaimableContextCount + 1.
  	self internalNewActiveContext: newContext.
   !

Item was changed:
  ----- Method: Interpreter>>justActivateNewMethod (in category 'callback support') -----
  justActivateNewMethod
  	"Activate the new method but *do not* copy receiver or arguments from activeContext."
  	| methodHeader initialIP newContext tempCount needsLarge where |
  	<inline: true>
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	needsLarge := methodHeader bitAnd: LargeContextBit.
  	(needsLarge = 0 and: [freeContexts ~= NilContext])
  		ifTrue: [newContext := freeContexts.
  				freeContexts := self fetchPointer: 0 ofObject: newContext]
  		ifFalse: ["Slower call for large contexts or empty free list"
  				newContext := self allocateOrRecycleContext: needsLarge].
+ 	initialIP := ((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1.
- 	initialIP := ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1.
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where := newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord) put: (self integerObjectOf: initialIP).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  
  	"Set the receiver..."
  	self longAt: where + (ReceiverIndex << ShiftForWord) put: receiver.
  
  	"clear all args and temps to nil in case it has been recycled"
  	needsLarge := nilObj.  "needsLarge here used just as faster (register?) temp"
  	ReceiverIndex + 1 to: tempCount + ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: needsLarge].
  	reclaimableContextCount := reclaimableContextCount + 1.
  
  	activeContext := newContext.
  	(self oop: newContext isLessThan: youngStart) ifTrue:
  		[self beRootIfOld: newContext].
  	self fetchContextRegisters: activeContext!

Item was removed:
- ----- Method: Interpreter>>literalCountOf: (in category 'compiled methods') -----
- literalCountOf: methodPointer
- 	^self literalCountOfHeader: (self headerOf: methodPointer)!

Item was removed:
- ----- Method: Interpreter>>literalCountOfHeader: (in category 'compiled methods') -----
- literalCountOfHeader: headerPointer
- 	^ (headerPointer >> 10) bitAnd: 16rFF!

Item was changed:
  ----- Method: Interpreter>>primitiveIndexOf: (in category 'compiled methods') -----
  primitiveIndexOf: methodPointer
  	"Note: We now have 10 bits of primitive index, but they are in two places
  	for temporary backward compatibility.  The time to unpack is negligible,
  	since the reconstituted full index is stored in the method cache."
  	| primBits |
+ 	primBits := ((self methodHeaderOf: methodPointer) >> 1) bitAnd: 16r100001FF.
- 	primBits := ((self headerOf: methodPointer) >> 1) bitAnd: 16r100001FF.
  	
+ 	^(primBits bitAnd: 16r1FF) + (primBits >> 19)!
- 	^ (primBits bitAnd: 16r1FF) + (primBits >> 19)
- !

Item was changed:
  ----- Method: Interpreter>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self popStack.
  	bytecodeCount := self popInteger.
  	self success: (self isIntegerObject: header).
  	successFlag ifFalse:
  		[self unPop: 2. ^nil].
  	class := self popStack.
+ 	size := (self literalCountOfMethodHeader: header) + 1 * BytesPerWord + bytecodeCount.
- 	size := (self literalCountOfHeader: header) + 1 * BytesPerWord + bytecodeCount.
  	theMethod := self instantiateClass: class indexableSize: size.
  	self storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
+ 	literalCount := self literalCountOfMethodHeader: header.
- 	literalCount := self literalCountOfHeader: header.
  	1 to: literalCount do:
  		[:i | self storePointer: i ofObject: theMethod withValue: nilObj].
  	self push: theMethod!

Item was changed:
  ----- Method: Interpreter>>tempCountOf: (in category 'compiled methods') -----
  tempCountOf: methodPointer
+ 	^((self methodHeaderOf: methodPointer) >> 19) bitAnd: 16r3F!
- 	^ ((self headerOf: methodPointer) >> 19) bitAnd: 16r3F!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self stackTop.
  	bytecodeCount := self stackIntegerValue: 1.
  	self success: (objectMemory isIntegerObject: header).
  	self successful ifFalse: [^nil].
  	class := self stackValue: 2.
+ 	literalCount := objectMemory literalCountOfMethodHeader: header.
+ 	size := literalCount + LiteralStart * BytesPerOop + bytecodeCount.
- 	literalCount := self literalCountOfHeader: header.
- 	size := literalCount + 1 * BytesPerWord + bytecodeCount.
  	theMethod := objectMemory instantiateClass: class indexableSize: size.
  	objectMemory storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
  	1 to: literalCount do:
  		[:i | objectMemory storePointer: i ofObject: theMethod withValue: objectMemory nilObject].
  	self pop: 3 thenPush: theMethod!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveObjectAt (in category 'object access primitives') -----
  primitiveObjectAt
  "Defined for CompiledMethods only"
  	| thisReceiver index |
  	index  := self stackIntegerValue: 0.
  	self successful ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	thisReceiver := self stackValue: 1.
+ 	(index > 0 and: [index <= ((objectMemory literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
- 	(index > 0 and: [index <= ((self literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	self pop: 2 thenPush: (objectMemory fetchPointer: index - 1 ofObject: thisReceiver)!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveObjectAtPut (in category 'object access primitives') -----
  primitiveObjectAtPut
  	"Store a literal into a CompiledMethod at the given index. Defined for CompiledMethods only."
  	| thisReceiver index newValue |
  	newValue := self stackValue: 0.
  	index := self stackValue: 1.
  	((objectMemory isNonIntegerObject: index)
  	 or: [index = ConstOne and: [(objectMemory isNonIntegerObject: newValue)]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	thisReceiver := self stackValue: 2.
+ 	(index > 0 and: [index <= ((objectMemory literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
- 	(index > 0 and: [index <= ((self literalCountOf: thisReceiver) + LiteralStart)]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadIndex].
  	objectMemory storePointer: index - 1 ofObject: thisReceiver withValue: newValue.
  	self pop: 3 thenPush: newValue!

Item was changed:
  ----- Method: NewCoObjectMemory>>copyObj:toSegment:addr:stopAt:saveOopAt:headerAt: (in category 'image segment in/out') -----
  copyObj: oop toSegment: segmentWordArray addr: lastSeg stopAt: stopAddr saveOopAt: oopPtr headerAt: hdrPtr
  	"Copy this object into the segment beginning at lastSeg.
  	Install a forwarding pointer, and save oop and header.
  	Fail if out of space.  Return the next segmentAddr if successful."
  
  	"Copy the object..."
  	| extraSize bodySize hdrAddr |
  	<inline: false>
  	self flag: #Dan.  "None of the imageSegment stuff has been updated for 64 bits"
  	extraSize := self extraHeaderBytes: oop.
  	bodySize := self sizeBitsOf: oop.
  	(self oop: (lastSeg + extraSize + bodySize) isGreaterThanOrEqualTo: stopAddr) ifTrue:
  		[^0]. "failure"
  	self transfer: extraSize + bodySize // BytesPerWord  "wordCount"
  		from: oop - extraSize
  		to: lastSeg+BytesPerWord.
  
  	"Clear root and mark bits of all headers copied into the segment"
  	hdrAddr := lastSeg+BytesPerWord + extraSize.
  	self longAt: hdrAddr put: ((self longAt: hdrAddr) bitAnd: AllButRootBit - MarkBit).
  
  	"Make sure Cogged methods have their true header field written to the segment."
  	((self isCompiledMethod: oop)
  	and: [coInterpreter methodHasCogMethod: oop]) ifTrue:
+ 		[self longAt: hdrAddr+BaseHeaderSize put: (self methodHeaderOf: oop)].
- 		[self longAt: hdrAddr+BaseHeaderSize put: (coInterpreter headerOf: oop)].
  
  	self forward: oop to: (lastSeg+BytesPerWord + extraSize - segmentWordArray)
  		savingOopAt: oopPtr
  		andHeaderAt: hdrPtr.
  
  	"Return new end of segment"
  	^lastSeg + extraSize + bodySize!

Item was added:
+ ----- Method: NewCoObjectMemory>>methodHeaderOf: (in category 'memory access') -----
+ methodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object.
+ 	 If the method has been cogged then the header is a pointer to
+ 	 the CogMethod and the real header will be stored in the CogMethod."
+ 	<inline: true>
+ 	| header |
+ 	self assert: (self isCompiledMethod: methodObj).
+ 	header := self fetchPointer: HeaderIndex ofObject: methodObj.
+ 	^(self isIntegerObject: header)
+ 		ifTrue: [header]
+ 		ifFalse:
+ 			[self assert: header asUnsignedInteger < coInterpreter heapBase.
+ 			 self assert: (coInterpreter cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod..
+ 			(coInterpreter cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was added:
+ ----- Method: NewCoObjectMemory>>noCheckMethodHeaderOf: (in category 'memory access') -----
+ noCheckMethodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object.
+ 	 If the method has been cogged then the header is a pointer to
+ 	 the CogMethod and the real header will be stored in the CogMethod."
+ 	<inline: true>
+ 	| header |
+ 	header := self fetchPointer: HeaderIndex ofObject: methodObj.
+ 	^(self isIntegerObject: header)
+ 		ifTrue: [header]
+ 		ifFalse:
+ 			[self assert: header asUnsignedInteger < coInterpreter heapBase.
+ 			 self assert: (self cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod..
+ 			(self cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was removed:
- ----- Method: NewCoObjectMemorySimulator>>literalCountOf: (in category 'simulation only') -----
- literalCountOf: anObj
- 	^coInterpreter literalCountOf: anObj!

Item was changed:
  ----- Method: NewObjectMemory>>lastPointerOf: (in category 'object enumeration') -----
+ lastPointerOf: objOop 
- lastPointerOf: oop 
  	"Return the byte offset of the last pointer field of the given object.  
  	 Can be used even when the type bits are not correct.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt header contextSize |
+ 	header := self baseHeader: objOop.
- 	| fmt header contextSize numLiterals |
- 	header := self baseHeader: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextHeader: header]) ifTrue:
  			["contexts end at the stack pointer"
+ 			contextSize := coInterpreter fetchStackPointerOf: objOop.
- 			contextSize := coInterpreter fetchStackPointerOf: oop.
  			^CtxtTempFrameStart + contextSize * BytesPerOop].
+ 		^(self sizeBitsOfSafe: objOop) - BaseHeaderSize  "all pointers"].
- 		^(self sizeBitsOfSafe: oop) - BaseHeaderSize  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	numLiterals := coInterpreter literalCountOf: oop.
- 	^numLiterals + LiteralStart * BytesPerOop!

Item was changed:
  ----- Method: NewObjectMemory>>lastPointerOf:recordWeakRoot: (in category 'object enumeration') -----
+ lastPointerOf: objOop recordWeakRoot: recordWeakRoot "<Boolean>"
- lastPointerOf: oop recordWeakRoot: recordWeakRoot "<Boolean>"
  	"Return the byte offset of the last pointer field of the given object.  
  	 Works with CompiledMethods, as well as ordinary objects. 
  	 Can be used even when the type bits are not correct.
  	 This is a version of lastPointerOf: for markAndTrace:.
  	 Already overridden to trace stack pages for the StackInterpreter.
  	 Override to ask coInterpreter to determine literalCount of methods."
+ 	| fmt sz header contextSize numOops |
- 	| fmt sz header contextSize numFields |
  	<inline: true>
  	<asmLabel: false>
+ 	header := self baseHeader: objOop.
- 	header := self baseHeader: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[fmt >= self indexablePointersFormat ifTrue:
  			[fmt = self lastPointerFormat ifTrue:
  				[(recordWeakRoot and: [weakRootCount >= 0]) ifTrue:
  					["And remember as weak root"
  					 (weakRootCount := weakRootCount + 1) <= WeakRootTableSize ifFalse:
  						[self error: 'weakRoots table overflow'].
+ 					 weakRoots at: weakRootCount put: objOop].
- 					 weakRoots at: weakRootCount put: oop].
  				"Do not trace the object's indexed fields if it's a weak class"
+ 				numOops := self nonWeakFieldsOf: objOop. "so nonWeakFieldsOf: may be inlined"
+ 				^numOops * BytesPerWord].
- 				numFields := self nonWeakFieldsOf: oop. "so nonWeakFieldsOf: may be inlined"
- 				^numFields * BytesPerWord].
  			"So fmt is 3"
  			(self isContextHeader: header) ifTrue:
+ 				[coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: objOop.
- 				[coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: oop.
  				 "contexts end at the stack pointer avoiding having to init fields beyond it"
+ 				 contextSize := coInterpreter fetchStackPointerOf: objOop.
+ 				 self assert: ReceiverIndex + contextSize < (self lengthOf: objOop baseHeader: header format: fmt).
- 				 contextSize := coInterpreter fetchStackPointerOf: oop.
- 				 self assert: ReceiverIndex + contextSize < (self lengthOf: oop baseHeader: header format: fmt).
  				 ^CtxtTempFrameStart + contextSize * BytesPerOop]].
+ 		 sz := self sizeBitsOfSafe: objOop.
- 		 sz := self sizeBitsOfSafe: oop.
  		 ^sz - BaseHeaderSize  "all pointers" ].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	numFields := coInterpreter literalCountOf: oop. "so literalCountOf: may be inlined"
- 	^numFields + LiteralStart * BytesPerOop!

Item was added:
+ ----- Method: NewObjectMemory>>lastPointerOfMethodHeader: (in category 'object enumeration') -----
+ lastPointerOfMethodHeader: methodHeader 
+ 	"Answer the byte offset of the last pointer field of a
+ 	 CompiledMethod with the given header.  Use a temp to
+ 	 allow inlining given MULTIPLEBYTECODESETS complications."
+ 	<inline: true>
+ 	<asmLabel: false>
+ 	| numLiterals |
+ 	numLiterals := self literalCountOfMethodHeader: methodHeader.
+ 	^numLiterals + LiteralStart - 1 * BytesPerOop + BaseHeaderSize!

Item was changed:
  ----- Method: NewObjectMemory>>lastPointerWhileForwarding: (in category 'gc -- compaction') -----
+ lastPointerWhileForwarding: objOop 
- lastPointerWhileForwarding: oop 
  	"The given object may have its header word in a forwarding block. Find  
  	 the offset of the last pointer in the object in spite of this obstacle."
+ 	| header fmt size contextSize |
- 	| header fmt size contextSize numLiterals |
  	<inline: true>
+ 	header := self headerWhileForwardingOf: objOop.
- 	header := self headerWhileForwardingOf: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextHeader: header]) ifTrue:
  			["contexts end at the stack pointer"
+ 			 contextSize := coInterpreter nacFetchStackPointerOf: objOop.
+ 			 self assert: ReceiverIndex + contextSize < (self lengthOf: objOop baseHeader: header format: fmt).
- 			 contextSize := coInterpreter nacFetchStackPointerOf: oop.
- 			 self assert: ReceiverIndex + contextSize < (self lengthOf: oop baseHeader: header format: fmt).
  			 ^CtxtTempFrameStart + contextSize * BytesPerOop].
  		 "do sizeBitsOf: using the header we obtained"
  		 size := (header bitAnd: TypeMask) = HeaderTypeSizeAndClass
+ 					ifTrue: [(self sizeHeader: objOop) bitAnd: AllButTypeMask]
- 					ifTrue: [(self sizeHeader: oop) bitAnd: AllButTypeMask]
  					ifFalse: [header bitAnd: SizeMask].
  		 ^size - BaseHeaderSize].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  	"CompiledMethod: contains both pointers and bytes"
+ 	self assert: (self isCompiledMethodHeader: header).
+ 	header := self noCheckMethodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	self assert: (header bitAnd: MarkBit) = 0.
- 	numLiterals := coInterpreter literalCountOf: oop.
- 	^numLiterals + LiteralStart * BytesPerOop!

Item was added:
+ ----- Method: NewObjectMemory>>literalCountOfMethodHeader: (in category 'memory access') -----
+ literalCountOfMethodHeader: header
+ 	<inline: true>
+ 	self assert: (self isIntegerObject: header).
+ 	^(coInterpreter headerIndicatesAlternateBytecodeSet: header)
+ 		ifTrue: [coInterpreter literalCountOfAlternateHeader: header]
+ 		ifFalse: [coInterpreter literalCountOfOriginalHeader: header]!

Item was removed:
- ----- Method: NewObjectMemorySimulator>>literalCountOf: (in category 'simulation only') -----
- literalCountOf: anObj
- 	^coInterpreter literalCountOf: anObj!

Item was changed:
  ----- Method: NewspeakInterpreter>>activateNewClosureMethod: (in category 'control primitives') -----
  activateNewClosureMethod: blockClosure
  	"Similar to activateNewMethod but for Closure and newMethod."
  	| theBlockClosure closureMethod newContext methodHeader numCopied where outerContext |
  
  	DoAssertionChecks ifTrue:
  		[self okayOop: blockClosure].
  	outerContext := self fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	DoAssertionChecks ifTrue:
  		[self okayOop: outerContext].
  	closureMethod := self fetchPointer: MethodIndex ofObject: outerContext.
+ 	methodHeader := self methodHeaderOf: closureMethod.
- 	methodHeader := self headerOf: closureMethod.
  	self pushRemappableOop: blockClosure.
  	newContext := self allocateOrRecycleContext: (methodHeader bitAnd: LargeContextBit). "All for one, and one for all!!"
  
  	"allocateOrRecycleContext: may cause a GC; restore blockClosure and refetch outerContext et al"
  	theBlockClosure := self popRemappableOop.
  	outerContext := self fetchPointer: ClosureOuterContextIndex ofObject: theBlockClosure.
  	numCopied := (self numSlotsOf: theBlockClosure) - ClosureFirstCopiedValueIndex.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where :=  newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord)
  		put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord)
  		put: (self fetchPointer: ClosureStartPCIndex ofObject: theBlockClosure).
  	self longAt: where + (StackPointerIndex << ShiftForWord)
  		put: (self integerObjectOf: argumentCount + numCopied).
  	self longAt: where + (MethodIndex << ShiftForWord)
  		put: (self fetchPointer: MethodIndex ofObject: outerContext).
  	self longAt: where + (ClosureIndex << ShiftForWord)
  		put: theBlockClosure.
  	self longAt: where + (ReceiverIndex << ShiftForWord)
  		put: (self fetchPointer: ReceiverIndex ofObject: outerContext).
  
  	"Copy the arguments..."
  	1 to: argumentCount do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord)
  				put: (self stackValue: argumentCount-i)].
  
  	"Copy the copied values..."
  	where := newContext + BaseHeaderSize + ((ReceiverIndex + 1 + argumentCount) << ShiftForWord).
  	0 to: numCopied - 1 do:
  		[:i| self longAt: where + (i << ShiftForWord)
  				put: (self fetchPointer: i + ClosureFirstCopiedValueIndex
  						  ofObject: theBlockClosure)].
  
  	"The initial instructions in the block nil-out remaining temps."
  
  	self pop: argumentCount + 1.
  	self newActiveContext: newContext!

Item was changed:
  ----- Method: NewspeakInterpreter>>activateNewMethod (in category 'message sending') -----
  activateNewMethod
  	| newContext methodHeader initialIP tempCount nilOop where errorCode |
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	newContext := self allocateOrRecycleContext: (methodHeader bitAnd: LargeContextBit).
  
+ 	initialIP := ((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1.
- 	initialIP := ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1.
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  
  	where :=  newContext  + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord) put: (self integerObjectOf: initialIP).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  	self longAt: where + (ClosureIndex << ShiftForWord) put: nilObj.
  
  	"Copy the receiver and arguments..."
  	0 to: argumentCount do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord) put: (self stackValue: argumentCount-i)].
  
  	"clear remaining temps to nil in case it has been recycled"
  	nilOop := nilObj.
  	argumentCount+1+ReceiverIndex to: tempCount+ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: nilOop].
  
  	"Pass primitive error code to last temp if method receives it (indicated
  	 by an initial long store temp bytecode).  Protect against obsolete values
  	 in primFailCode by checking that newMethod actually has a primitive?"
  	primFailCode > 0 ifTrue:
  		[((self primitiveIndexOfMethodHeader: methodHeader) > 0
  		   and: [(self fetchByte: initialIP - 1 ofObject: newMethod) = 129 "long store temp"]) ifTrue:
  			[errorCode := self fetchPointer: primFailCode - 1 ofObject: (self splObj: PrimErrTableIndex).
  			 self longAt: where + ((tempCount+ReceiverIndex) << ShiftForWord)
  				put: errorCode "nil if primFailCode == 1, or primFailCode"].
  		primFailCode := 0].
  
  	self pop: argumentCount + 1.
  	reclaimableContextCount := reclaimableContextCount + 1.
  	self newActiveContext: newContext.!

Item was changed:
  ----- Method: NewspeakInterpreter>>argumentCountOf: (in category 'compiled methods') -----
  argumentCountOf: methodPointer
+ 	^((self methodHeaderOf: methodPointer) >> 25) bitAnd: 16r0F!
- 	^ ((self headerOf: methodPointer) >> 25) bitAnd: 16r0F!

Item was removed:
- ----- Method: NewspeakInterpreter>>headerOf: (in category 'compiled methods') -----
- headerOf: methodPointer
- 	^self fetchPointer: HeaderIndex ofObject: methodPointer!

Item was changed:
  ----- Method: NewspeakInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader initialIP newContext tempCount argCount2 needsLarge where |
  	<inline: true>
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	needsLarge := methodHeader bitAnd: LargeContextBit.
  	(needsLarge = 0 and: [freeContexts ~= NilContext])
  		ifTrue: [newContext := freeContexts.
  				freeContexts := self fetchPointer: 0 ofObject: newContext]
  		ifFalse: ["Slower call for large contexts or empty free list"
  				self externalizeIPandSP.
  				newContext := self allocateOrRecycleContext: needsLarge.
  				self internalizeIPandSP].
+ 	initialIP := ((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1.
- 	initialIP := ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1.
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where :=   newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord) put: (self integerObjectOf: initialIP).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  	self longAt: where + (ClosureIndex << ShiftForWord) put: nilObj.
  
  	"Copy the receiver and arguments..."
  	argCount2 := argumentCount.
  	0 to: argCount2 do:
  		[:i | self longAt: where + ((ReceiverIndex+i) << ShiftForWord) put: (self internalStackValue: argCount2-i)].
  
  	"clear remaining temps to nil in case it has been recycled"
  	needsLarge := nilObj.  "needsLarge here used just as faster (register?) temp"
  	argCount2+1+ReceiverIndex to: tempCount+ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: needsLarge].
  
  	"Pass primitive error code to last temp if method receives it (indicated
  	 by an initial long store temp bytecode).  Protect against obsolete values
  	 in primFailCode by checking that newMethod actually has a primitive?"
  	primFailCode > 0 ifTrue:
  		[((self primitiveIndexOfMethodHeader: methodHeader) > 0
  		  and: [(self fetchByte: initialIP - 1 ofObject: newMethod) = 129 "long store temp"]) ifTrue:
  			[needsLarge := self fetchPointer: primFailCode - 1 ofObject: (self splObj: PrimErrTableIndex).
  			 self longAt: where + ((tempCount+ReceiverIndex) << ShiftForWord)
  				put: needsLarge "nil if primFailCode == 1, or primFailCode"].
  		primFailCode := 0].
  
  	self internalPop: argCount2 + 1.
  	reclaimableContextCount := reclaimableContextCount + 1.
  	self internalNewActiveContext: newContext.
   !

Item was changed:
  ----- Method: NewspeakInterpreter>>justActivateNewMethod (in category 'callback support') -----
  justActivateNewMethod
  	"Activate the new method but *do not* copy receiver or arguments from activeContext."
  	| methodHeader initialIP newContext tempCount needsLarge where |
  	<inline: true>
  
+ 	methodHeader := self methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	needsLarge := methodHeader bitAnd: LargeContextBit.
  	(needsLarge = 0 and: [freeContexts ~= NilContext])
  		ifTrue: [newContext := freeContexts.
  				freeContexts := self fetchPointer: 0 ofObject: newContext]
  		ifFalse: ["Slower call for large contexts or empty free list"
  				newContext := self allocateOrRecycleContext: needsLarge].
+ 	initialIP := ((LiteralStart + (self literalCountOfMethodHeader: methodHeader)) * BytesPerWord) + 1.
- 	initialIP := ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerWord) + 1.
  	tempCount := (methodHeader >> 19) bitAnd: 16r3F.
  
  	"Assume: newContext will be recorded as a root if necessary by the
  	 call to newActiveContext: below, so we can use unchecked stores."
  	where := newContext + BaseHeaderSize.
  	self longAt: where + (SenderIndex << ShiftForWord) put: activeContext.
  	self longAt: where + (InstructionPointerIndex << ShiftForWord) put: (self integerObjectOf: initialIP).
  	self longAt: where + (StackPointerIndex << ShiftForWord) put: (self integerObjectOf: tempCount).
  	self longAt: where + (MethodIndex << ShiftForWord) put: newMethod.
  
  	"Set the receiver..."
  	self longAt: where + (ReceiverIndex << ShiftForWord) put: receiver.
  
  	"clear all args and temps to nil in case it has been recycled"
  	needsLarge := nilObj.  "needsLarge here used just as faster (register?) temp"
  	ReceiverIndex + 1 to: tempCount + ReceiverIndex do:
  		[:i | self longAt: where + (i << ShiftForWord) put: needsLarge].
  	reclaimableContextCount := reclaimableContextCount + 1.
  
  	activeContext := newContext.
  	(self oop: newContext isLessThan: youngStart) ifTrue:
  		[self beRootIfOld: newContext].
  	self fetchContextRegisters: activeContext!

Item was removed:
- ----- Method: NewspeakInterpreter>>literalCountOf: (in category 'compiled methods') -----
- literalCountOf: methodPointer
- 	^self literalCountOfHeader: (self headerOf: methodPointer)!

Item was removed:
- ----- Method: NewspeakInterpreter>>literalCountOfHeader: (in category 'compiled methods') -----
- literalCountOfHeader: headerPointer
- 	^ (headerPointer >> 10) bitAnd: 16rFF!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveDoNamedPrimitiveWithArgs (in category 'plugin primitives') -----
  primitiveDoNamedPrimitiveWithArgs
  	"Simulate an primitiveExternalCall invocation (e.g. for the Debugger).  Do not cache anything.
  	 e.g. ContextPart>>tryNamedPrimitiveIn: aCompiledMethod for: aReceiver withArgs: arguments"
  	| argumentArray arraySize index methodArg methodHeader spec
  	  moduleName functionName moduleLength functionLength addr |
  	<var: #addr declareC: 'void (*addr)()'>
  
  	argumentArray := self stackTop.
  	(self isArray: argumentArray) ifFalse:
  		[^self primitiveFail]. "invalid args"
  	arraySize := self numSlotsOf: argumentArray.
  	self success: (self roomToPushNArgs: arraySize).
  
  	methodArg := self stackObjectValue: 2.
  	self successful ifFalse:
  		[^self primitiveFail]. "invalid args"
  
  	(self isCompiledMethod: methodArg) ifFalse:
  		[^self primitiveFail]. "invalid args"
  
+ 	methodHeader := self methodHeaderOf: methodArg.
- 	methodHeader := self headerOf: methodArg.
  
+ 	(self literalCountOfMethodHeader: methodHeader) > 2 ifFalse:
- 	(self literalCountOfHeader: methodHeader) > 2 ifFalse:
  		[^self primitiveFail]. "invalid methodArg state"
  	self assertClassOf: (spec := self fetchPointer: 1 "first literal" ofObject: methodArg)
  		is: (self splObj: ClassArray).
  	(self successful
  	and: [(self lengthOf: spec) = 4
  	and: [(self primitiveIndexOfMethodHeader: methodHeader) = 117]]) ifFalse:
  		[^self primitiveFail]. "invalid methodArg state"
  
  	(self argumentCountOfMethodHeader: methodHeader) = arraySize ifFalse:
  		[^self primitiveFail]. "invalid args (Array args wrong size)"
  
  	"The function has not been loaded yet. Fetch module and function name."
  	moduleName := self fetchPointer: 0 ofObject: spec.
  	moduleName = nilObj
  		ifTrue: [moduleLength := 0]
  		ifFalse: [self success: (self isBytes: moduleName).
  				moduleLength := self lengthOf: moduleName.
  				self cCode: '' inSmalltalk:
  					[ (#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: (self stringOf: moduleName)) "??"
  						ifTrue: [moduleLength := 0  "Cause all of these to fail"]]].
  	functionName := self fetchPointer: 1 ofObject: spec.
  	self success: (self isBytes: functionName).
  	functionLength := self lengthOf: functionName.
  	self successful ifFalse: [^self primitiveFail]. "invalid methodArg state"
  
  	addr := self ioLoadExternalFunction: functionName + BaseHeaderSize
  				OfLength: functionLength
  				FromModule: moduleName + BaseHeaderSize
  				OfLength: moduleLength.
  	addr = 0 ifTrue:
  		[^self primitiveFail]. "could not find function"
  
  	"Cannot fail this primitive from now on.  Can only fail the external primitive."
  	self pop: 1.
  	argumentCount := arraySize.
  	index := 1.
  	[index <= arraySize] whileTrue:
  		[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
  		 index := index + 1].
  
  	"Run the primitive (sets primFailCode)"
  	self pushRemappableOop: argumentArray. "prim might alloc/gc in callback"
  	lkupClass := nilObj.
  	self callExternalPrimitive: addr.
  	argumentArray := self popRemappableOop.
  	self successful ifFalse: "If primitive failed, then restore state for failure code"
  		[self pop: arraySize thenPush: argumentArray.
  		 argumentCount := 3]!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveIndexOf: (in category 'compiled methods') -----
  primitiveIndexOf: methodPointer
  	"Note: We now have 10 bits of primitive index, but they are in two places
  	for temporary backward compatibility.  The time to unpack is negligible,
  	since the reconstituted full index is stored in the method cache."
  	| primBits |
+ 	primBits := ((self methodHeaderOf: methodPointer) >> 1) bitAnd: 16r100001FF.
- 	primBits := ((self headerOf: methodPointer) >> 1) bitAnd: 16r100001FF.
  	
+ 	^(primBits bitAnd: 16r1FF) + (primBits >> 19)!
- 	^ (primBits bitAnd: 16r1FF) + (primBits >> 19)
- !

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveNewMethod (in category 'compiled methods') -----
  primitiveNewMethod
  	| header bytecodeCount class size theMethod literalCount |
  	header := self popStack.
  	bytecodeCount := self popInteger.
  	self success: (self isIntegerObject: header).
  	self successful ifFalse:
  		[self unPop: 2. ^nil].
  	class := self popStack.
+ 	size := (self literalCountOfMethodHeader: header) + 1 * BytesPerWord + bytecodeCount.
- 	size := (self literalCountOfHeader: header) + 1 * BytesPerWord + bytecodeCount.
  	theMethod := self instantiateClass: class indexableSize: size.
  	self storePointerUnchecked: HeaderIndex ofObject: theMethod withValue: header.
+ 	literalCount := self literalCountOfMethodHeader: header.
- 	literalCount := self literalCountOfHeader: header.
  	1 to: literalCount do:
  		[:i | self storePointerUnchecked: i ofObject: theMethod withValue: nilObj].
  	self push: theMethod!

Item was changed:
  ----- Method: NewspeakInterpreter>>roomToPushNArgs: (in category 'primitive support') -----
  roomToPushNArgs: n
  	"Answer if there is room to push n arguments onto the current stack.
  	 There may be room in this stackPage but there may not be room if
  	 the frame were converted into a context."
  	| cntxSize |
+ 	((self methodHeaderOf: method) bitAnd: LargeContextBit) ~= 0
- 	((self headerOf: method) bitAnd: LargeContextBit) ~= 0
  		ifTrue: [cntxSize := LargeContextSize / BytesPerWord - ReceiverIndex]
  		ifFalse: [cntxSize := SmallContextSize / BytesPerWord - ReceiverIndex].
  	^self stackPointerIndex + n <= cntxSize!

Item was changed:
  ----- Method: NewspeakInterpreter>>tempCountOf: (in category 'compiled methods') -----
  tempCountOf: methodPointer
+ 	^((self methodHeaderOf: methodPointer) >> 19) bitAnd: 16r3F!
- 	^ ((self headerOf: methodPointer) >> 19) bitAnd: 16r3F!

Item was added:
+ ----- Method: ObjectMemory>>bootstrapping (in category 'accessing') -----
+ bootstrapping
+ 	^false!

Item was changed:
  ----- Method: ObjectMemory>>lastPointerOf: (in category 'object enumeration') -----
+ lastPointerOf: objOop 
- lastPointerOf: oop 
  	"Return the byte offset of the last pointer field of the given object.  
  	Works with CompiledMethods, as well as ordinary objects. 
  	Can be used even when the type bits are not correct."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt sz header contextSize |
+ 	header := self baseHeader: objOop.
- 	| fmt sz methodHeader header contextSize |
- 	header := self baseHeader: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextHeader: header])
  					ifTrue: ["contexts end at the stack pointer"
+ 						contextSize := self fetchStackPointerOf: objOop.
- 						contextSize := self fetchStackPointerOf: oop.
  						^ CtxtTempFrameStart + contextSize * BytesPerWord].
+ 				sz := self sizeBitsOfSafe: objOop.
- 				sz := self sizeBitsOfSafe: oop.
  				^sz - BaseHeaderSize "all pointers"].
+ 	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
- 	fmt < self firstCompiledMethodFormat ifTrue: [^ 0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes:"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	methodHeader := self longAt: oop + BaseHeaderSize.
- 	^(methodHeader >> 10 bitAnd: 255) + LiteralStart * BytesPerWord!

Item was changed:
  ----- Method: ObjectMemory>>lastPointerOf:recordWeakRoot: (in category 'gc -- mark and sweep') -----
+ lastPointerOf: objOop recordWeakRoot: recordWeakRoot "<Boolean>"
- lastPointerOf: oop recordWeakRoot: recordWeakRoot "<Boolean>"
  	"Return the byte offset of the last pointer field of the given object.  
  	 Works with CompiledMethods, as well as ordinary objects. 
  	 Can be used even when the type bits are not correct.
  	 This is a version of lastPointerOf: for markAndTrace:."
+ 	| fmt sz header contextSize |
- 	| fmt sz header contextSize numLiterals |
  	<inline: true>
+ 	header := self baseHeader: objOop.
- 	header := self baseHeader: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[fmt >= self indexablePointersFormat ifTrue:
  			[fmt = self lastPointerFormat ifTrue:
  				[(recordWeakRoot and: [weakRootCount >= 0]) ifTrue:
  					["And remember as weak root"
  					 (weakRootCount := weakRootCount + 1) <= WeakRootTableSize ifFalse:
  						[self error: 'weakRoots table overflow'].
+ 					 weakRoots at: weakRootCount put: objOop].
- 					 weakRoots at: weakRootCount put: oop].
  				"Do not trace the object's indexed fields if it's a weak class"
+ 				^(self nonWeakFieldsOf: objOop) * BytesPerOop].
- 				^(self nonWeakFieldsOf: oop) * BytesPerOop].
  			"So fmt is 3"
  			(self isContextHeader: header) ifTrue:
  				["contexts end at the stack pointer avoiding having to init fields beyond it"
+ 				 contextSize := self fetchStackPointerOf: objOop.
- 				 contextSize := self fetchStackPointerOf: oop.
  				 ^CtxtTempFrameStart + contextSize * BytesPerOop]].
+ 		 sz := self sizeBitsOfSafe: objOop.
- 		 sz := self sizeBitsOfSafe: oop.
  		 ^sz - BaseHeaderSize  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes:"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	numLiterals := self literalCountOf: oop.
- 	^numLiterals + LiteralStart * BytesPerOop!

Item was added:
+ ----- Method: ObjectMemory>>lastPointerOfMethodHeader: (in category 'object enumeration') -----
+ lastPointerOfMethodHeader: methodHeader 
+ 	"Answer the byte offset of the last pointer field of a
+ 	 CompiledMethod with the given header."
+ 	<inline: true>
+ 	<asmLabel: false>
+ 	^(self literalCountOfMethodHeader: methodHeader)
+ 	  + LiteralStart - 1 * BytesPerOop + BaseHeaderSize!

Item was changed:
  ----- Method: ObjectMemory>>lastPointerWhileForwarding: (in category 'gc -- compaction') -----
+ lastPointerWhileForwarding: objOop 
- lastPointerWhileForwarding: oop 
  	"The given object may have its header word in a forwarding block. Find  
  	the offset of the last pointer in the object in spite of this obstacle. "
+ 	| header fmt size contextSize |
- 	| header fmt size methodHeader contextSize |
  	<inline: true>
+ 	header := self headerWhileForwardingOf: objOop.
- 	header := self headerWhileForwardingOf: oop.
  	fmt := self formatOfHeader: header.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextHeader: header]) ifTrue:
  			["contexts end at the stack pointer"
+ 			contextSize := self nacFetchStackPointerOf: objOop.
+ 			self assert: ReceiverIndex + contextSize < (self lengthOf: objOop baseHeader: header format: fmt).
- 			contextSize := self nacFetchStackPointerOf: oop.
- 			self assert: ReceiverIndex + contextSize < (self lengthOf: oop baseHeader: header format: fmt).
  			^CtxtTempFrameStart + contextSize * BytesPerWord].
  		"do sizeBitsOf: using the header we obtained"
  		(header bitAnd: TypeMask) = HeaderTypeSizeAndClass
+ 			ifTrue: [size := (self sizeHeader: objOop) bitAnd: AllButTypeMask]
- 			ifTrue: [size := (self sizeHeader: oop) bitAnd: AllButTypeMask]
  			ifFalse: [size := header bitAnd: SizeMask].
  		^size - BaseHeaderSize].
+ 	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
+ 	"CompiledMethod: contains both pointers and bytes"
+ 	self assert: (self isCompiledMethodHeader: header).
+ 	header := self noCheckMethodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	fmt < self firstCompiledMethodFormat ifTrue: [^ 0]. "no pointers"
- 	methodHeader := self longAt: oop + BaseHeaderSize.
- 	^(self literalCountOfHeader: methodHeader) * BytesPerWord + BaseHeaderSize!

Item was added:
+ ----- Method: ObjectMemory>>literalCountOf: (in category 'method access') -----
+ literalCountOf: methodPointer
+ 	<api>
+ 	^self literalCountOfMethodHeader: (self methodHeaderOf: methodPointer)!

Item was added:
+ ----- Method: ObjectMemory>>literalCountOfMethodHeader: (in category 'memory access') -----
+ literalCountOfMethodHeader: header
+ 	<inline: true>
+ 	self assert: (self isIntegerObject: header).
+ 	^header >> 10 bitAnd: 16rFF!

Item was added:
+ ----- Method: ObjectMemory>>methodHeaderOf: (in category 'method access') -----
+ methodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object."
+ 	self assert: (self isCompiledMethod: methodObj).
+ 	^self fetchPointer: HeaderIndex ofObject: methodObj!

Item was added:
+ ----- Method: ObjectMemory>>noCheckMethodHeaderOf: (in category 'method access') -----
+ noCheckMethodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object."
+ 	^self fetchPointer: HeaderIndex ofObject: methodObj!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
+ 	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
  		(2 139 139 genPushExplicitOuterReceiverBytecode isMapped)	"Newspeak"
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"SimpleStackBasedCogit initializeBytecodeTableForNewspeakV4"
  
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
+ 	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode)
  		(1  79   79 genPushConstantOneBytecode)
  
  		(1   80 101 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
  		(1 176 183 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtStoreReceiverVariableBytecode)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 callPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"SimpleStackBasedCogit initializeBytecodeTableForSistaV1"
  
+ 	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushLiteralVariable16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode)
  		(1  76   76 genPushReceiverBytecode)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1   96 117 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"SimpleStackBasedCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
+ 	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode)
  		(1  16   31 genPushTemporaryVariableBytecode)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(1 126 127 unknownBytecode)
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
  		(1 139 139 unknownBytecode)
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 197 genSpecialSelectorSend isMapped)
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped)
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

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 := objectMemory methodHeaderOf: methodObj.
- 	methodHeader := coInterpreter headerOf: methodObj.
  	backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  	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 temporaryCountOfMethodHeader: methodHeader) do:
  		[:i|
  		self PushR: SendNumArgsReg].
  	(primitiveIndex > 0
  	 and: [(coInterpreter longStoreBytecodeForHeader: methodHeader)
  			= (objectMemory
  				fetchByte: initialPC + (coInterpreter sizeOfCallPrimitiveBytecode: methodHeader)
  				ofObject: 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.
  	self cppIf: #NewspeakVM ifTrue:
  		[numIRCs > 0 ifTrue:
  		 	[self PrefetchAw: theIRCs]]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>firstSpecialSelectorBytecodeOffset (in category 'bytecode generators') -----
  firstSpecialSelectorBytecodeOffset
  	<inline: true>
  	^self cppIf: MULTIPLEBYTECODESETS
+ 		ifTrue: [bytecodeSetOffset = 256 ifTrue: [AltFirstSpecialSelector + 256] ifFalse: [FirstSpecialSelector]]
+ 		ifFalse: [FirstSpecialSelector]!
- 		ifTrue: [bytecodeSetOffset = 256 ifTrue: [80 + 256] ifFalse: [176]]
- 		ifFalse: [176]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>methodHeaderOf: (in category 'growing/shrinking memory') -----
+ methodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object.
+ 	 If the method has been cogged then the header is a pointer to
+ 	 the CogMethod and the real header will be stored in the CogMethod."
+ 	<inline: true>
+ 	| header |
+ 	self assert: (self isCompiledMethod: methodObj).
+ 	header := self fetchPointer: HeaderIndex ofObject: methodObj.
+ 	^(self isIntegerObject: header)
+ 		ifTrue: [header]
+ 		ifFalse:
+ 			[self assert: header asUnsignedInteger < newSpaceStart.
+ 			 self assert: (self cCoerceSimple: header to: #'CogMethod *') objectHeader
+ 						= self nullHeaderForMachineCodeMethod..
+ 			(self cCoerceSimple: header to: #'CogMethod *') methodHeader]!

Item was changed:
  ----- Method: Spur32BitCoMemoryManager>>smallIntegerTag (in category 'cog jit support') -----
  smallIntegerTag
+ 	"Beware, SmallInteger tags are 1 or 3.  But SmallInteger's identityHash is 1."
- 	"Beware, SmallInetger tags are 1 or 3.  But SmallInteger's identityHash is 1."
  	<api>
  	^1!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>setHashBitsOf:to: (in category 'header access') -----
  setHashBitsOf: objOop to: hash
  	self flag: #endianness.
+ 	self assert: (hash bitAnd: self identityHashHalfWordMask) = hash.
+ 	self cCode: [self deny: ((self classAtIndex: hash) ~= objOop
+ 							and: [coInterpreter addressCouldBeClassObj: objOop])]
+ 		inSmalltalk:
+ 			[coInterpreter ifNotNil:
+ 				[self deny: ((self classAtIndex: hash) ~= objOop
+ 							and: [coInterpreter addressCouldBeClassObj: objOop])]].
- 	self assert: (hash between: 0 and: self identityHashHalfWordMask).
  	self longAt: objOop + 4
  		put: ((self longAt: objOop + 4) bitClear: self identityHashHalfWordMask) + hash!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>setHashBitsOf:to: (in category 'header access') -----
  setHashBitsOf: objOop to: hash
+ 	self assert: (hash bitAnd: self identityHashFullWordMask) = hash.
+ 	self cCode: [self deny: ((self classAtIndex: hash) ~= objOop
+ 							and: [coInterpreter addressCouldBeClassObj: objOop])]
+ 		inSmalltalk:
+ 			[coInterpreter ifNotNil:
+ 				[self deny: ((self classAtIndex: hash) ~= objOop
+ 							and: [coInterpreter addressCouldBeClassObj: objOop])]].
- 	self assert: (hash between: 0 and: self identityHashFullWordMask).
  	self longAt: objOop
  		put: ((self longAt: objOop) bitClear: self identityHashFullWordMask) + hash!

Item was changed:
  ----- Method: SpurMemoryManager>>lastPointerOf: (in category 'object enumeration') -----
  lastPointerOf: objOop 
  	"Answer the byte offset of the last pointer field of the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt contextSize header |
- 	| fmt contextSize numLiterals |
  	fmt := self formatOf: objOop.
  	self assert: fmt ~= self forwardedFormat.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextNonImm: objOop]) ifTrue:
  			["contexts end at the stack pointer"
  			contextSize := coInterpreter fetchStackPointerOf: objOop.
  			^CtxtTempFrameStart + contextSize * BytesPerOop].
  		^(self numSlotsOf: objOop) - 1 * BytesPerOop + self baseHeaderSize  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	numLiterals := coInterpreter literalCountOf: objOop.
- 	^numLiterals + LiteralStart - 1 * BytesPerOop + self baseHeaderSize!

Item was added:
+ ----- Method: SpurMemoryManager>>lastPointerOfMethodHeader: (in category 'object enumeration') -----
+ lastPointerOfMethodHeader: methodHeader 
+ 	"Answer the byte offset of the last pointer field of a
+ 	 CompiledMethod with the given header."
+ 	<inline: true>
+ 	<asmLabel: false>
+ 	^(self literalCountOfMethodHeader: methodHeader)
+ 	  + LiteralStart - 1 * BytesPerOop + self baseHeaderSize!

Item was changed:
  ----- Method: SpurMemoryManager>>lastPointerOfWhileSwizzling: (in category 'snapshot') -----
  lastPointerOfWhileSwizzling: objOop 
  	"Answer the byte offset of the last pointer field of the given object.
  	 Works with CompiledMethods, as well as ordinary objects.
  	 Does not examine the stack pointer of contexts to be sure to swizzle
  	 the nils that fill contexts on snapshot.
  	 It is invariant that on image load no object contains a forwarding pointer,
  	 and the image contains no forwarders (see class comment)."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt header |
- 	| fmt numLiterals |
  	fmt := self formatOf: objOop.
  	self assert: fmt ~= self forwardedFormat.
  	fmt <= self lastPointerFormat ifTrue:
+ 		[^(self numSlotsOf: objOop) - 1 * self bytesPerOop + self baseHeaderSize  "all pointers"].
- 		[^(self numSlotsOf: objOop) - 1 * BytesPerOop + self baseHeaderSize  "all pointers"].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	^self lastPointerOfMethodHeader: header!
- 	numLiterals := coInterpreter literalCountOf: objOop.
- 	^numLiterals + LiteralStart - 1 * BytesPerOop + self baseHeaderSize!

Item was added:
+ ----- Method: SpurMemoryManager>>literalCountOf: (in category 'method access') -----
+ literalCountOf: methodPointer
+ 	<api>
+ 	^self literalCountOfMethodHeader: (self methodHeaderOf: methodPointer)!

Item was added:
+ ----- Method: SpurMemoryManager>>literalCountOfMethodHeader: (in category 'method access') -----
+ literalCountOfMethodHeader: header
+ 	<inline: true>
+ 	self assert: (self isIntegerObject: header).
+ 	^(self integerValueOf: header) bitAnd: 16rFFFF!

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

Item was added:
+ ----- Method: SpurMemoryManager>>methodHeaderOf: (in category 'memory access') -----
+ methodHeaderOf: methodObj
+ 	"Answer the method header of a CompiledMethod object."
+ 	self assert: (self isCompiledMethod: methodObj).
+ 	^self fetchPointer: HeaderIndex ofObject: methodObj!

Item was changed:
  ----- Method: SpurMemoryManager>>numPointerSlotsOf: (in category 'object access') -----
  numPointerSlotsOf: objOop
  	"Answer the number of pointer fields in the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<api>
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt contextSize numLiterals header |
- 	| fmt contextSize numLiterals |
  	fmt := self formatOf: objOop.
  	fmt <= self lastPointerFormat ifTrue:
  		[(fmt = self indexablePointersFormat
  		  and: [self isContextNonImm: objOop]) ifTrue:
  			["contexts end at the stack pointer"
  			contextSize := coInterpreter fetchStackPointerOf: objOop.
  			^CtxtTempFrameStart + contextSize].
  		^self numSlotsOf: objOop  "all pointers"].
  	fmt = self forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	numLiterals := self literalCountOfMethodHeader: header.
- 	numLiterals := coInterpreter literalCountOf: objOop.
  	^numLiterals + LiteralStart!

Item was changed:
  ----- Method: SpurMemoryManager>>numStrongSlotsOf:format:ephemeronInactiveIf: (in category 'object access') -----
  numStrongSlotsOf: objOop format: fmt ephemeronInactiveIf: criterion
  	"Answer the number of strong pointer fields in the given object.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<var: 'criterion' declareC: 'int (*criterion)(sqInt key)'>
  	<inline: true>
  	<asmLabel: false>
+ 	| numSlots  contextSize numLiterals header |
- 	| numSlots  contextSize numLiterals |
  	fmt <= self lastPointerFormat ifTrue:
  		[numSlots := self numSlotsOf: objOop.
  		 fmt <= self arrayFormat ifTrue:
  			[^numSlots].
  		 fmt = self indexablePointersFormat ifTrue:
  			[(self isContextNonImm: objOop) ifTrue:
  				[coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: objOop.
  				 "contexts end at the stack pointer"
  				 contextSize := coInterpreter fetchStackPointerOf: objOop.
  				 ^CtxtTempFrameStart + contextSize].
  			 ^numSlots].
  		 fmt = self weakArrayFormat ifTrue:
  			[^self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop)].
  		 self assert: fmt = self ephemeronFormat.
  		 ^(self perform: criterion with: (self keyOfEphemeron: objOop))
  			ifTrue: [numSlots]
  			ifFalse: [0]].
  	fmt = self forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	numLiterals := self literalCountOfMethodHeader: header.
- 	numLiterals := coInterpreter literalCountOf: objOop.
  	^numLiterals + LiteralStart!

Item was changed:
  ----- Method: SpurMemoryManager>>numStrongSlotsOfInephemeral: (in category 'object access') -----
  numStrongSlotsOfInephemeral: objOop
  	"Answer the number of strong pointer fields in the given object,
  	 which is .expected not to be an active ephemeron.
  	 Works with CompiledMethods, as well as ordinary objects."
  	<inline: true>
  	<asmLabel: false>
+ 	| fmt numSlots  contextSize numLiterals header |
- 	| fmt numSlots  contextSize numLiterals |
  	fmt := self formatOf: objOop.
  	self assert: (fmt ~= self ephemeronFormat or: [self isMarked: (self keyOfEphemeron: objOop)]).
  	fmt <= self lastPointerFormat ifTrue:
  		[numSlots := self numSlotsOf: objOop.
  		 fmt <= self arrayFormat ifTrue:
  			[^numSlots].
  		 fmt = self indexablePointersFormat ifTrue:
  			[(self isContextNonImm: objOop) ifTrue:
  				[coInterpreter setTraceFlagOnContextsFramesPageIfNeeded: objOop.
  				 "contexts end at the stack pointer"
  				 contextSize := coInterpreter fetchStackPointerOf: objOop.
  				 ^CtxtTempFrameStart + contextSize].
  			 ^numSlots].
  		 fmt = self weakArrayFormat ifTrue:
  			[^self fixedFieldsOfClass: (self fetchClassOfNonImm: objOop)]].
  	fmt = self forwardedFormat ifTrue: [^1].
  	fmt < self firstCompiledMethodFormat ifTrue: [^0]. "no pointers"
  
  	"CompiledMethod: contains both pointers and bytes"
+ 	header := self methodHeaderOf: objOop.
+ 	numLiterals := self literalCountOfMethodHeader: header.
- 	numLiterals := coInterpreter literalCountOf: objOop.
  	^numLiterals + LiteralStart!

Item was changed:
  ----- Method: StackDepthFinder>>callPrimitive: (in category 'instruction decoding') -----
  callPrimitive: primitiveIndex
+ 	"Call Primitive bytecode."
+ 	self drop: (encoderClass stackDeltaForPrimitive: primitiveIndex in: self method) negated!
- 	"Call Primitive bytecode.  Effectively a no-op."!

Item was changed:
  ----- Method: StackInterpreter class>>writeVMHeaderTo:bytesPerWord: (in category 'translation') -----
  writeVMHeaderTo: aStream bytesPerWord: bytesPerWord
  	super writeVMHeaderTo: aStream bytesPerWord: bytesPerWord.
+ 	SistaVM ifTrue:
+ 		[aStream nextPutAll: '#define SistaVM 1'; cr].
  	NewspeakVM ifTrue:
  		[aStream nextPutAll: '#define NewspeakVM 1'; cr].
  	MULTIPLEBYTECODESETS ifTrue:
  		[aStream nextPutAll: '#define MULTIPLEBYTECODESETS 1'; cr].
  	IMMUTABILITY ifTrue:
  		[aStream nextPutAll: '#define IMMUTABILITY 1'; cr].
  	NewspeakVM | MULTIPLEBYTECODESETS | IMMUTABILITY ifTrue:
  		[aStream cr].
  	aStream nextPutAll: '#define STACKVM 1'; cr.
  	(initializationOptions at: #SpurObjectMemory ifAbsent: false) ifTrue:
  		[aStream nextPutAll: '#define SPURVM 1'; cr]!

Item was changed:
  ----- Method: StackInterpreter>>argumentCountOf: (in category 'compiled methods') -----
  argumentCountOf: methodPointer
  	<api>
+ 	^self argumentCountOfMethodHeader: (objectMemory methodHeaderOf: methodPointer)!
- 	^self argumentCountOfMethodHeader: (self headerOf: methodPointer)!

Item was changed:
  ----- Method: StackInterpreter>>checkOkayFields: (in category 'debug support') -----
  checkOkayFields: oop
  	"Check if the argument is an ok object.
  	 If this is a pointers object, check that its fields are all okay oops."
  
  	| hasYoung i fieldOop |
  	(oop = nil or: [oop = 0]) ifTrue: [ ^true ]. "?? eem 1/16/2013"
  	(objectMemory isIntegerObject: oop) ifTrue: [ ^true ].
  	(objectMemory checkOkayOop: oop) ifFalse: [ ^false ].
  	(objectMemory checkOopHasOkayClass: oop) ifFalse: [ ^false ].
  	((objectMemory isPointersNonImm: oop) or: [objectMemory isCompiledMethod: oop]) ifFalse: [ ^true ].
  	hasYoung := objectMemory hasSpurMemoryManagerAPI not
  				  and: [objectMemory isYoung: (objectMemory fetchClassOfNonImm: oop)].
  	(objectMemory isCompiledMethod: oop)
  		ifTrue:
+ 			[i := (objectMemory literalCountOf: oop) + LiteralStart - 1]
- 			[i := (self literalCountOf: oop) + LiteralStart - 1]
  		ifFalse:
  			[(objectMemory isContext: oop)
  				ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
  				ifFalse: [i := (objectMemory lengthOf: oop) - 1]].
  	[i >= 0] whileTrue:
  		[fieldOop := objectMemory fetchPointer: i ofObject: oop.
  		(objectMemory isIntegerObject: fieldOop) ifFalse:
  			[hasYoung := hasYoung or: [objectMemory isYoung: fieldOop].
  			(objectMemory checkOkayOop: fieldOop) ifFalse: [ ^false ].
  			(self checkOopHasOkayClass: fieldOop) ifFalse: [ ^false ]].
  		i := i - 1].
  	hasYoung ifTrue:
  		[^objectMemory checkOkayYoungReferrer: oop].
  	^true!

Item was changed:
  ----- 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.
+ 	^(objectMemory hasSpurMemoryManagerAPI or: [MULTIPLEBYTECODESETS])
+ 		ifTrue:
+ 			[pc = encodedip
+ 			or: [| methodHeader |
+ 				methodHeader := objectMemory methodHeaderOf: (objectMemory fetchPointer: MethodIndex ofObject: aContext).
+ 				(self methodHeaderHasPrimitive: methodHeader)
+ 				and: [(objectMemory integerValueOf: encodedip) - (objectMemory integerValueOf: pc)
+ 					= (self sizeOfCallPrimitiveBytecode: methodHeader)]]]
- 	^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 changed:
  ----- Method: StackInterpreter>>firstByteIndexOfMethod: (in category 'compiled methods') -----
  firstByteIndexOfMethod: methodObj
  	"Answer the one-relative index of the first bytecode in methodObj.
  	 Used for safer bounds-checking on methods."
+ 	^(objectMemory literalCountOf: methodObj) + LiteralStart * BytesPerOop + 1!
- 	^(self literalCountOf: methodObj) + LiteralStart * BytesPerOop + 1!

Item was changed:
  ----- Method: StackInterpreter>>firstBytecodeOfAlternateHeader:method: (in category 'compiled methods') -----
  firstBytecodeOfAlternateHeader: methodHeader method: theMethod
+ 	^theMethod
+ 	 + ((LiteralStart + (self literalCountOfAlternateHeader: methodHeader)) * objectMemory bytesPerOop)
+ 	 + objectMemory baseHeaderSize!
- 	^theMethod + ((LiteralStart + (self literalCountOfAlternateHeader: methodHeader)) * BytesPerWord) + BaseHeaderSize!

Item was changed:
  ----- Method: StackInterpreter>>flushExternalPrimitiveOf: (in category 'plugin primitive support') -----
  flushExternalPrimitiveOf: methodObj
  	"methodObj is a CompiledMethod containing an external primitive. Flush the function address and session ID of the CM"
  	| lit |
+ 	(objectMemory literalCountOf: methodObj) > 0 ifFalse:
- 	(self literalCountOf: methodObj) > 0 ifFalse:
  		[^nil]. "Something's broken"
  	lit := self literal: 0 ofMethod: methodObj.
  	((objectMemory isArray: lit) and:[(objectMemory lengthOf: lit) = 4]) ifFalse:
  		[^nil]. "Something's broken"
  	"ConstZero is a known SmallInt so no root check needed"
  	objectMemory storePointerUnchecked: 2 ofObject: lit withValue: ConstZero.
  	objectMemory storePointerUnchecked: 3 ofObject: lit withValue: ConstZero!

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

Item was changed:
  ----- 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: (((LiteralStart + (objectMemory literalCountOf: aMethod)) * BytesPerOop)) + 1
- 	self assert: (ip between: (((LiteralStart + (self literalCountOf: aMethod)) * BytesPerOop)) + 1
  					and: (objectMemory lengthOf: aMethod)).
  	^aMethod + ip + objectMemory baseHeaderSize - 2!

Item was changed:
  ----- Method: StackInterpreter>>initialPCForHeader:method: (in category 'compiled methods') -----
  initialPCForHeader: methodHeader method: theMethod
  	<api>
  	^theMethod
+ 	+ ((LiteralStart + (objectMemory literalCountOfMethodHeader: methodHeader)) * BytesPerOop)
- 	+ ((LiteralStart + (self literalCountOfHeader: methodHeader)) * BytesPerOop)
  	+ objectMemory baseHeaderSize!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr errorCode |
  	<inline: true>
  
+ 	methodHeader := objectMemory methodHeaderOf: newMethod.
- 	methodHeader := self headerOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	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:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self internalStackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	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: [(objectMemory literalCountOf: aMethodObj) > 0]) ifFalse:
- 	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]]]!

Item was changed:
  ----- Method: StackInterpreter>>justActivateNewMethod (in category 'message sending') -----
  justActivateNewMethod
  	| methodHeader numArgs numTemps rcvr errorCode |
  	<inline: true>
+ 	methodHeader := objectMemory methodHeaderOf: newMethod.
- 	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 assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	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:
  				[errorCode := self getErrorObjectFromPrimFailCode.
  				 self stackTopPut: errorCode "nil if primFailCode == 1, or primFailCode"].
  			 primFailCode := 0]].
  
  	^methodHeader!

Item was removed:
- ----- Method: StackInterpreter>>literalCountOf: (in category 'compiled methods') -----
- literalCountOf: methodPointer
- 	^self literalCountOfHeader: (self headerOf: methodPointer)!

Item was removed:
- ----- Method: StackInterpreter>>literalCountOfHeader: (in category 'compiled methods') -----
- literalCountOfHeader: headerPointer
- 	<api>
- 	"We support two method header formats, as selected by the sign flag.  Even if the VM only
- 	 has one bytecode set, supporting teh two formats here allows for instantiating methods in
- 	 the other format for testing, etc."
- 	^(self headerIndicatesAlternateBytecodeSet: headerPointer)
- 		ifTrue: [self literalCountOfAlternateHeader: headerPointer]
- 		ifFalse: [self literalCountOfOriginalHeader: headerPointer]!

Item was changed:
  ----- Method: StackInterpreter>>lookupMethodInClass: (in category 'message sending') -----
  lookupMethodInClass: class
  	| currentClass dictionary found |
  	<inline: false>
  	self assert: (self addressCouldBeClassObj: class).
  	currentClass := class.
+ 	[currentClass ~= objectMemory nilObject] whileTrue:
- 	[currentClass ~= objectMemory nilObject]
- 		whileTrue:
  		[dictionary := objectMemory followObjField: MethodDictionaryIndex ofObject: currentClass.
  		dictionary = objectMemory nilObject ifTrue:
  			["MethodDict pointer is nil (hopefully due a swapped out stub)
  				-- raise exception #cannotInterpret:."
  			self createActualMessageTo: class.
  			messageSelector := objectMemory splObj: SelectorCannotInterpret.
  			self sendBreakpoint: messageSelector receiver: nil.
  			^self lookupMethodInClass: (self superclassOf: currentClass)].
  		found := self lookupMethodInDictionary: dictionary.
  		found ifTrue: [^currentClass].
  		currentClass := self superclassOf: currentClass].
  
  	"Could not find #doesNotUnderstand: -- unrecoverable error."
  	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue:
  		[self error: 'Recursive not understood error encountered'].
  
  	"Cound not find a normal message -- raise exception #doesNotUnderstand:"
  	self createActualMessageTo: class.
  	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
  	self sendBreak: messageSelector + BaseHeaderSize
  		point: (objectMemory lengthOf: messageSelector)
  		receiver: nil.
  	^self lookupMethodInClass: class!

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 rcvr |
  	<inline: false>
  	<var: #page type: #'StackPage *'>
  	<var: #pointer type: #'char *'>
  	self assert: (self isSingleContext: aContext).
  	self assert: (objectMemory goodContextSize: aContext).
  	page := self newStackPage.
  	pointer := page baseAddress.
  	theIP := objectMemory fetchPointer: InstructionPointerIndex ofObject: aContext.
  	theMethod := objectMemory followObjField: MethodIndex ofObject: aContext.
  	(objectMemory isIntegerObject: theIP) ifFalse:
  		[self error: 'context is not resumable'].
  	theIP := objectMemory integerValueOf: theIP.
  	rcvr := objectMemory followField: ReceiverIndex ofObject: 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 followField: ClosureIndex ofObject: aContext.
  	maybeClosure ~= objectMemory nilObject
  		ifTrue:
  			[numArgs := self argumentCountOfClosure: maybeClosure.
  			 stackPages longAt: pointer put: maybeClosure]
  		ifFalse:
  			[| header |
+ 			 header := objectMemory methodHeaderOf: theMethod.
- 			 header := self headerOf: theMethod.
  			 numArgs := self argumentCountOfMethodHeader: header.
+ 			 "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)].
- 			 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)]].
  			 stackPages longAt: pointer put: rcvr].
  	"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: rcvr.
  	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.
  	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 validStackPageBaseFrame: page).
  	^page!

Item was changed:
  ----- Method: StackInterpreter>>marryFrame:SP:copyTemps: (in category 'frame access') -----
  marryFrame: theFP SP: theSP copyTemps: copyTemps
  	"Marry an unmarried frame.  This means creating a spouse context
  	 initialized with a subset of the frame's state that references the frame.
  	 For the default closure implementation we do not need to copy temps.
  	 Different closure implementations may require temps to be copied."
  	| theContext methodHeader numSlots numArgs numStack closureOrNil numTemps |
  	<inline: true>
  	<var: #theFP type: #'char *'>
  	<var: #theSP type: #'char *'>
  	self assert: (self frameHasContext: theFP) not.
  
  	"The SP is expected to be pointing at the last oop on the stack, not at the pc"
  	self assert: (objectMemory addressCouldBeOop: (stackPages longAt: theSP)).
  
+ 	methodHeader := objectMemory methodHeaderOf: (self frameMethod: theFP).
- 	methodHeader := self headerOf: (self frameMethod: theFP).
  	"Decide how much of the stack to preserve in widowed contexts.  Preserving too much
  	 state will potentially hold onto garbage.  Holding onto too little may mean that a dead
  	 context isn't informative enough in a debugging situation.  If copyTemps is false (as it
  	 is in the default closure implementation) compromise, retaining only the arguments with
  	 no temporaries.  Note that we still set the stack pointer to its current value, but stack
  	 contents other than the arguments are nil."
  	numArgs := self frameNumArgs: theFP.
  	numStack := self stackPointerIndexForFrame: theFP WithSP: theSP.
  
  	closureOrNil := (self frameIsBlockActivation: theFP)
  						ifTrue: [self pushedReceiverOrClosureOfFrame: theFP]
  						ifFalse: [objectMemory nilObject].
  
+ 	numSlots := (self methodHeaderIndicatesLargeFrame: methodHeader)
- 	numSlots := (methodHeader bitAnd: LargeContextBit) ~= 0
  					ifTrue: [LargeContextSlots]
  					ifFalse: [SmallContextSlots].
  	theContext := objectMemory eeInstantiateMethodContextSlots: numSlots.
  	self assert: numStack + ReceiverIndex <= numSlots. 
  	"Mark context as married by setting its sender to the frame pointer plus SmallInteger
  	 tags and the InstructionPointer to the saved fp (which ensures correct alignment
  	 w.r.t. the frame when we check for validity)"
  	objectMemory storePointerUnchecked: SenderIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: theFP).
  	objectMemory storePointerUnchecked: InstructionPointerIndex
  		ofObject: theContext
  		withValue: (self withSmallIntegerTags: (self frameCallerFP: theFP)).
  	objectMemory storePointerUnchecked: StackPointerIndex
  		ofObject: theContext
  		withValue: (objectMemory integerObjectOf: numStack).
  	objectMemory storePointerUnchecked: MethodIndex
  		ofObject: theContext
  		withValue: (self frameMethod: theFP).
  	objectMemory storePointerUnchecked: ClosureIndex ofObject: theContext withValue: closureOrNil.
  	objectMemory storePointerUnchecked: ReceiverIndex
  		ofObject: theContext
  		withValue: (self frameReceiver: theFP).
  	"If copyTemps is false, store just the arguments.  If the frame is divorced the context
  	 will have valid arguments but all temporaries will be nil."
  	1 to: numArgs do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext "inline self temporary: i - 1 in:theFP" 
  			withValue: (stackPages longAt: theFP
  										+ FoxCallerSavedIP
  										+ ((numArgs - i + 1) * BytesPerWord))].
  	copyTemps ifTrue:
  		[numTemps := self frameNumTemps: theFP.
  		 1 to: numTemps do:
  			[:i|
  			objectMemory storePointerUnchecked: ReceiverIndex + i + numArgs
  				ofObject: theContext
  				withValue: (self temporary: i - 1 in: theFP)].
  		 numArgs := numArgs + numTemps].
  
  	numArgs + 1 to: numStack do:
  		[:i|
  		objectMemory storePointerUnchecked: ReceiverIndex + i
  			ofObject: theContext
  			withValue: objectMemory nilObject].
  
  	self setFrameContext: theFP to: theContext.
  	self setFrameHasContext: theFP.
  
  	self assert: (self frameHasContext: theFP).
  	self assert: (self frameOfMarriedContext: theContext) = theFP.
  	self assert: numStack + ReceiverIndex < (objectMemory lengthOf: theContext).
  
  	^theContext
  !

Item was changed:
  ----- Method: StackInterpreter>>methodClassAssociationOf: (in category 'compiled methods') -----
  methodClassAssociationOf: methodPointer
  	<api>
+ 	^self literal: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer!
- 	^self literal: (self literalCountOf: methodPointer) - 1 ofMethod: methodPointer!

Item was changed:
  ----- Method: StackInterpreter>>methodClassOf: (in category 'compiled methods') -----
  methodClassOf: methodPointer
  	<api>
  	"Using a read barrier here simplifies the become implementation and costs very little
  	 because the class index and ValueIndex of the association almost certainly share a cache line."
  	^self cppIf: NewspeakVM
  		ifTrue:
  			[| literal |
+ 			 literal := self followLiteral: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
- 			 literal := self followLiteral: (self literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
  			 literal = objectMemory nilObject
  				ifTrue: [literal]
  				ifFalse: [objectMemory followField: ValueIndex ofObject: literal]]
  		ifFalse:
  			[| literal |
+ 			 literal := self followLiteral: (objectMemory literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
- 			 literal := self followLiteral: (self literalCountOf: methodPointer) - 1 ofMethod: methodPointer.
  			 objectMemory followField: ValueIndex ofObject: literal]!

Item was changed:
  ----- Method: StackInterpreter>>methodHeaderHasPrimitive: (in category 'compiled methods') -----
  methodHeaderHasPrimitive: methodHeader
  	"Note: We now have 10 bits of primitive index, but they are in two places
  	 for temporary backward compatibility.  The time to unpack is negligible,
  	 since the derived primitive function pointer is stored in the method cache."
+ 	^objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue: [self alternateHeaderHasPrimitiveFlag: methodHeader]
+ 		ifFalse:
+ 			[MULTIPLEBYTECODESETS
+ 				ifTrue:
+ 					[(self headerIndicatesAlternateBytecodeSet: methodHeader)
+ 						ifTrue: [self alternateHeaderHasPrimitiveFlag: methodHeader]
+ 						ifFalse: [(methodHeader bitAnd: 16r200003FE) ~= 0]]
+ 				ifFalse:
+ 					[(methodHeader bitAnd: 16r200003FE) ~= 0]]!
- 	^self
- 		cppIf: MULTIPLEBYTECODESETS
- 		ifTrue: [(self headerIndicatesAlternateBytecodeSet: methodHeader)
- 				ifTrue: [self alternateHeaderHasPrimitiveFlag: methodHeader]
- 				ifFalse: [(methodHeader bitAnd: 16r200003FE) ~= 0]]
- 		ifFalse: [(methodHeader bitAnd: 16r200003FE) ~= 0]!

Item was added:
+ ----- Method: StackInterpreter>>methodHeaderIndicatesLargeFrame: (in category 'frame access') -----
+ methodHeaderIndicatesLargeFrame: methodHeader
+ 	<inline: true>
+ 	^(methodHeader bitAnd: LargeContextBit) ~= 0!

Item was changed:
  ----- Method: StackInterpreter>>methodUsesAlternateBytecodeSet: (in category 'internal interpreter access') -----
  methodUsesAlternateBytecodeSet: aMethodObj
  	<api>
  	<inline: true>
  	"A negative header selects the alternate bytecode set."
+ 	^self headerIndicatesAlternateBytecodeSet: (objectMemory methodHeaderOf: aMethodObj)!
- 	^self headerIndicatesAlternateBytecodeSet: (self headerOf: aMethodObj)!

Item was changed:
  ----- Method: StackInterpreter>>okayFields: (in category 'debug support') -----
  okayFields: oop
  	"Check if the argument is an ok object.
  	 If this is a pointers object, check that its fields are all okay oops."
  
  	| i fieldOop |
  	(oop = nil or: [oop = 0]) ifTrue: [ ^true ].
  	(objectMemory isIntegerObject: oop) ifTrue: [ ^true ].
  	(objectMemory okayOop: oop) ifFalse: [ ^false ].
  	(objectMemory oopHasOkayClass: oop) ifFalse: [ ^false ].
  	((objectMemory isPointersNonImm: oop) or: [objectMemory isCompiledMethod: oop]) ifFalse: [ ^true ].
  	(objectMemory isCompiledMethod: oop)
  		ifTrue:
+ 			[i := (objectMemory literalCountOf: oop) + LiteralStart - 1]
- 			[i := (self literalCountOf: oop) + LiteralStart - 1]
  		ifFalse:
  			[(objectMemory isContext: oop)
  				ifTrue: [i := CtxtTempFrameStart + (self fetchStackPointerOf: oop) - 1]
  				ifFalse: [i := (objectMemory lengthOf: oop) - 1]].
  	[i >= 0] whileTrue: [
  		fieldOop := objectMemory fetchPointer: i ofObject: oop.
  		(objectMemory isIntegerObject: fieldOop) ifFalse: [
  			(objectMemory okayOop: fieldOop) ifFalse: [ ^false ].
  			(self oopHasOkayClass: fieldOop) ifFalse: [ ^false ].
  		].
  		i := i - 1.
  	].
  	^true!

Item was changed:
  ----- Method: StackInterpreter>>penultimateLiteralOf: (in category 'debug printing') -----
  penultimateLiteralOf: aMethodOop
  	<api>
  	self assert: (objectMemory isOopCompiledMethod: aMethodOop).
+ 	^self literal: (objectMemory literalCountOf: aMethodOop) - 2 ofMethod: aMethodOop!
- 	^self literal: (self literalCountOf: aMethodOop) - 2 ofMethod: aMethodOop!

Item was changed:
  ----- Method: StackInterpreter>>primitiveIndexOf: (in category 'compiled methods') -----
  primitiveIndexOf: methodPointer
  	<api>
+ 	^self primitiveIndexOfMethod: methodPointer header: (objectMemory methodHeaderOf: methodPointer)!
- 	^self primitiveIndexOfMethod: methodPointer header: (self headerOf: methodPointer)!

Item was changed:
  ----- Method: StackInterpreter>>primitiveIndexOfMethod:header: (in category 'compiled methods') -----
  primitiveIndexOfMethod: theMethod header: methodHeader
  	"Note: With the Squeak V0 format we now have 10 bits of primitive index, but they are in
  	 two places for temporary backward compatibility.  The time to unpack is negligible,
  	 since the derived primitive function pointer is stored in the method cache.  With the new
  	 format we assume a 3-byte CallPrimitive with a little-endian 16-bit primitive index."
  	<api>
  	<inline: true>
+ 	| firstBytecode |
+ 	^objectMemory hasSpurMemoryManagerAPI
- 	^self cppIf: MULTIPLEBYTECODESETS
  		ifTrue:
+ 			[(self alternateHeaderHasPrimitiveFlag: methodHeader)
- 			[(self headerIndicatesAlternateBytecodeSet: methodHeader)
  				ifTrue:
+ 					[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
+ 					 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
+ 				ifFalse:
+ 					[0]]
+ 		ifFalse:
+ 			[MULTIPLEBYTECODESETS
+ 				ifTrue:
+ 					[(self headerIndicatesAlternateBytecodeSet: methodHeader)
- 					[(self alternateHeaderHasPrimitiveFlag: methodHeader)
  						ifTrue:
+ 							[(self alternateHeaderHasPrimitiveFlag: methodHeader)
+ 								ifTrue:
+ 									[firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
+ 									 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
+ 								ifFalse:
+ 									[0]]
- 							[| firstBytecode |
- 							 firstBytecode := self firstBytecodeOfAlternateHeader: methodHeader method: theMethod.
- 							 (objectMemory byteAt: firstBytecode + 1) + ((objectMemory byteAt: firstBytecode + 2) << 8)]
  						ifFalse:
+ 							[| primBits |
+ 							 primBits := objectMemory integerValueOf: methodHeader.
+ 							 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]
- 							[0]]
  				ifFalse:
  					[| primBits |
+ 					 primBits := objectMemory integerValueOf: methodHeader.
+ 					 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]!
- 					 primBits := methodHeader >> 1.
- 					 (primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]]
- 		ifFalse:
- 			[| primBits |
- 			primBits := methodHeader >> 1.
- 			(primBits bitAnd: 16r1FF) + (primBits >> 19 bitAnd: 16r200)]!

Item was changed:
  ----- Method: StackInterpreter>>roomToPushNArgs: (in category 'primitive support') -----
  roomToPushNArgs: n
  	"Answer if there is room to push n arguments onto the current stack.  We assume
  	 this is called by primitives that check there is enough room in any new context, and
  	 won't actually push the arguments in the current context if the primitive fails.  With
  	 this assumption it is safe to answer based on the maximum argument count, /not/
  	 the ammount of space in the current frame were it converted to a context.."
  	false
  		ifTrue: "old code that checked size of context..."
  			[| cntxSize |
  			 self assert: method = (stackPages longAt: framePointer + FoxMethod).
+ 			 cntxSize := (self methodHeaderIndicatesLargeFrame: (objectMemory methodHeaderOf: method))
- 			 cntxSize := ((self headerOf: method) bitAnd: LargeContextBit) ~= 0
  							ifTrue: [LargeContextSlots - CtxtTempFrameStart]
  							ifFalse: [SmallContextSlots - CtxtTempFrameStart].
  			 ^self stackPointerIndex + n <= cntxSize]
  		ifFalse: "simpler code that simply insists args are <= max arg count"
  			[^n <= (LargeContextSlots - CtxtTempFrameStart)]!

Item was changed:
  ----- 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: (objectMemory methodHeaderOf: method) = methodHeader.
- 	self assert: (self headerOf: method) = methodHeader.
  	self cppIf: MULTIPLEBYTECODESETS
  		ifTrue: [bytecodeSetSelector := (self headerIndicatesAlternateBytecodeSet: methodHeader)
  											ifTrue: [256]
  											ifFalse: [0]]!

Item was changed:
  ----- Method: StackInterpreter>>setMethodClassAssociationOf:to: (in category 'compiled methods') -----
  setMethodClassAssociationOf: methodPointer to: anObject
  	objectMemory
+ 		storePointer: (objectMemory literalCountOf: methodPointer) + LiteralStart - 1
- 		storePointer: (self literalCountOf: methodPointer) + LiteralStart - 1
  		ofObject: methodPointer
  		withValue: anObject!

Item was changed:
  ----- Method: StackInterpreter>>sizeOfCallPrimitiveBytecode: (in category 'compiled methods') -----
  sizeOfCallPrimitiveBytecode: methodHeader
  	"Answer if the method starts with a long store temp bytecode, which indicates it has a primitive error code."
  	"249		11111001	i i i i i i i i	jjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjjj * 256)"
  	<api>
  	<inline: true>
+ 	^objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue: [3]
+ 		ifFalse:
+ 			[MULTIPLEBYTECODESETS
+ 				ifTrue: [(self headerIndicatesAlternateBytecodeSet: methodHeader)
+ 							ifTrue: [3]
+ 							ifFalse: [0]]
+ 				ifFalse: [0]]!
- 	^self
- 		cppIf: MULTIPLEBYTECODESETS
- 		ifTrue: [(self headerIndicatesAlternateBytecodeSet: methodHeader)
- 					ifTrue: [3]
- 					ifFalse: [0]]
- 		ifFalse: [0]!

Item was changed:
  ----- Method: StackInterpreter>>startPCOfMethod: (in category 'compiled methods') -----
  startPCOfMethod: aCompiledMethod
  	<api>
  	"Zero-relative version of CompiledMethod>>startpc."
+ 	^(objectMemory literalCountOf: aCompiledMethod) + LiteralStart * objectMemory bytesPerOop!
- 	^(self literalCountOf: aCompiledMethod) + LiteralStart * objectMemory bytesPerOop!

Item was changed:
  ----- Method: StackInterpreter>>tempCountOf: (in category 'compiled methods') -----
  tempCountOf: methodPointer
  	<api>
+ 	^self temporaryCountOfMethodHeader: (objectMemory methodHeaderOf: methodPointer)!
- 	^self temporaryCountOfMethodHeader: (self headerOf: methodPointer)!

Item was changed:
  ----- Method: StackInterpreter>>updateObjectsPostByteSwap (in category 'image save/restore') -----
  updateObjectsPostByteSwap
  	"Byte-swap the words of all bytes objects in the image, including Strings, ByteArrays,
  	 and CompiledMethods. This returns these objects to their original byte ordering
  	 after blindly byte-swapping the entire image. For compiled  methods, byte-swap
  	 only their bytecodes part. Ensure floats are in platform-order."
  	| swapFloatWords |
  	swapFloatWords := objectMemory vmEndianness ~= imageFloatsBigEndian.
  	self assert: ClassFloatCompactIndex ~= 0.
  	objectMemory allObjectsDo:
  		[:oop| | fmt wordAddr methodHeader temp |
  		fmt := objectMemory formatOf: oop.
  		 fmt >= self firstByteFormat ifTrue: "oop contains bytes"
  			[wordAddr := oop + BaseHeaderSize.
  			fmt >= self firstCompiledMethodFormat ifTrue: "compiled method; start after methodHeader and literals"
  				[methodHeader := self longAt: oop + BaseHeaderSize.
+ 				 wordAddr := wordAddr + (((objectMemory literalCountOfMethodHeader: methodHeader) + LiteralStart) * BytesPerOop)].
- 				 wordAddr := wordAddr + (((self literalCountOfHeader: methodHeader) + LiteralStart) * BytesPerWord)].
  			objectMemory reverseBytesFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)].
  		 fmt = self firstLongFormat ifTrue: "Bitmap, Float etc"
  			[(swapFloatWords
  			  and: [(objectMemory compactClassIndexOf: oop) = ClassFloatCompactIndex])
  				ifTrue:
  					[temp := self longAt: oop + BaseHeaderSize.
  					 self longAt: oop + BaseHeaderSize put: (self longAt: oop + BaseHeaderSize + 4).
  					 self longAt: oop + BaseHeaderSize + 4 put: temp]
  				ifFalse:
  					[BytesPerWord = 8 ifTrue: "Object contains 32-bit half-words packed into 64-bit machine words."
  						[wordAddr := oop + BaseHeaderSize.
  						 objectMemory reverseWordsFrom: wordAddr to: oop + (objectMemory sizeBitsOf: oop)]]]]!

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

Item was changed:
  ----- Method: StackInterpreterPrimitives>>pathTo:using:followWeak: (in category 'object access primitives') -----
  pathTo: goal using: stack followWeak: followWeak
  	"Trace objects and frames from the root, marking visited objects, pushing the current path on stack, until goal is found.
  	 If found, unmark, leaving path in stack, and answer 0.  Otherwise answer an error:
  		PrimErrBadArgument if stack is not an Array
  		PrimErrBadIndex if search overflows stack
  		PrimErrNotFound if goal cannot be found"
  	| current index next stackSize stackp freeStartAtStart |
  	(objectMemory isArray: stack) ifFalse:
  		[^PrimErrBadArgument].
  	self assert: objectMemory allObjectsUnmarked.
  	freeStartAtStart := objectMemory freeStart. "check no allocations during search"
  	objectMemory beRootIfOld: stack. "so no store checks are necessary on stack"
  	stackSize := objectMemory lengthOf: stack.
  	objectMemory mark: stack.
  	"no need. the current context is not reachable from the active process (suspendedContext is nil)"
  	"objectMemory mark: self activeProcess."
  	current := objectMemory specialObjectsOop.
  	objectMemory mark: current.
  	index := objectMemory lengthOf: current.
  	stackp := 0.
  	[[(index := index - 1) >= -1] whileTrue:
  		[(stackPages couldBeFramePointer: current)
  			ifTrue:
  				[next := index >= 0
  							ifTrue: [self field: index ofFrame: (self cCoerceSimple: current to: #'char *')]
  							ifFalse: [objectMemory nilObject]]
  			ifFalse:
  				[index >= 0
  					ifTrue:
  						[next := (objectMemory isContextNonImm: current)
  									ifTrue: [self fieldOrSenderFP: index ofContext: current]
  									ifFalse: [objectMemory fetchPointer: index ofObject: current]]
  					ifFalse:
  						[next := objectMemory fetchClassOfNonImm: current]].
  		 (stackPages couldBeFramePointer: next)
  			ifTrue: [self assert: (self isFrame: next onPage: (stackPages stackPageFor: next))]
  			ifFalse: [self assert: (self checkOkayOop: next)].
  		 next = goal ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory storePointer: stackp ofObject: stack withValue: current.
  			 self pruneStack: stack stackp: stackp.
  			 ^0].
  		 ((objectMemory isNonIntegerObject: next)
  		  and: [(stackPages couldBeFramePointer: next)
  				ifTrue: [(self frameIsMarked: next) not]
  				ifFalse:
  					[(objectMemory isMarked: next) not
  					  and: [((objectMemory isPointers: next) or: [objectMemory isCompiledMethod: next])
  					  and: [followWeak or: [(objectMemory isWeakNonImm: next) not]]]]])
  			ifTrue:
  				[stackp + 2 > stackSize ifTrue:
  					[self assert: freeStartAtStart = objectMemory freeStart.
  					 self unmarkAfterPathTo.
  					 objectMemory nilFieldsOf: stack.
  					 ^PrimErrBadIndex]. "PrimErrNoMemory ?"
  				 objectMemory
  					storePointerUnchecked: stackp ofObject: stack withValue: current;
  					storePointerUnchecked: stackp + 1 ofObject: stack withValue: (objectMemory integerObjectOf: index).
  				 stackp := stackp + 2.
  				 (stackPages couldBeFramePointer: (self cCoerceSimple: next to: #'char *'))
  					ifTrue:
  						[self markFrame: next.
  						index := self fieldsInFrame: (self cCoerceSimple: next to: #'char *')]
  					ifFalse:
  						[objectMemory mark: next.
  						 (objectMemory isCompiledMethod: next)
+ 							ifTrue: [index := (objectMemory literalCountOf: next) + LiteralStart]
- 							ifTrue: [index := (self literalCountOf: next) + LiteralStart]
  							ifFalse: [index := objectMemory lengthOf: next]].
  				 current := next]].
  		 current = objectMemory specialObjectsOop ifTrue:
  			[self assert: freeStartAtStart = objectMemory freeStart.
  			 self unmarkAfterPathTo.
  			 objectMemory nilFieldsOf: stack.
  			^PrimErrNotFound].
  		 index := objectMemory integerValueOf: (objectMemory fetchPointer: stackp - 1 ofObject: stack).
  		 current := objectMemory fetchPointer: stackp - 2 ofObject: stack.
  		 stackp := stackp - 2] repeat!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveDoNamedPrimitiveWithArgs (in category 'plugin primitives') -----
  primitiveDoNamedPrimitiveWithArgs
  	"Simulate an primitiveExternalCall invocation (e.g. for the Debugger).  Do not cache anything.
  	 e.g. ContextPart>>tryNamedPrimitiveIn: aCompiledMethod for: aReceiver withArgs: arguments"
  	| argumentArray arraySize methodArg methodHeader
  	  moduleName functionName moduleLength functionLength
  	  spec addr primRcvr ctxtRcvr isArray |
  	<var: #addr declareC: 'void (*addr)()'>
  	argumentArray := self stackTop.
  	methodArg := self stackValue: 2.
  	((objectMemory isArray: argumentArray)
  	 and: [objectMemory isOopCompiledMethod: methodArg]) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  	arraySize := objectMemory numSlotsOf: argumentArray.
  	(self roomToPushNArgs: arraySize) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  
+ 	methodHeader := objectMemory methodHeaderOf: methodArg.
+ 	(objectMemory literalCountOfMethodHeader: methodHeader) > 2 ifFalse:
- 	methodHeader := self headerOf: methodArg.
- 	(self literalCountOfHeader: methodHeader) > 2 ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  	spec := objectMemory fetchPointer: 1 "first literal" ofObject: methodArg.
  	isArray := self isInstanceOfClassArray: spec.
  	(isArray
  	and: [(objectMemory lengthOf: spec) = 4
  	and: [(self primitiveIndexOfMethod: methodArg header: methodHeader) = 117]]) ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	(self argumentCountOfMethodHeader: methodHeader) = arraySize ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args (Array args wrong size)"
  
  	"The function has not been loaded yet. Fetch module and function name."
  	moduleName := objectMemory fetchPointer: 0 ofObject: spec.
  	moduleName = objectMemory nilObject
  		ifTrue: [moduleLength := 0]
  		ifFalse: [self success: (objectMemory isBytes: moduleName).
  				moduleLength := objectMemory lengthOf: moduleName.
  				self cCode: '' inSmalltalk:
  					[ (#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: (self stringOf: moduleName)) "??"
  						ifTrue: [moduleLength := 0  "Cause all of these to fail"]]].
  	functionName := objectMemory fetchPointer: 1 ofObject: spec.
  	self success: (objectMemory isBytes: functionName).
  	functionLength := objectMemory lengthOf: functionName.
  	self successful ifFalse: [^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	addr := self ioLoadExternalFunction: functionName + BaseHeaderSize
  				OfLength: functionLength
  				FromModule: moduleName + BaseHeaderSize
  				OfLength: moduleLength.
  	addr = 0 ifTrue:
  		[^self primitiveFailFor: -1]. "could not find function; answer generic failure (see below)"
  
  	"Cannot fail this primitive from now on.  Can only fail the external primitive."
  	objectMemory pushRemappableOop: (argumentArray := self popStack).
  	objectMemory pushRemappableOop: (primRcvr := self popStack).
  	objectMemory pushRemappableOop: self popStack. "the method"
  	objectMemory pushRemappableOop: self popStack. "the context receiver"
  	self push: primRcvr. "replace context receiver with actual receiver"
  	argumentCount := arraySize.
  	1 to: arraySize do:
  		[:index| self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray)].
  	self callExternalPrimitive: addr.
  	ctxtRcvr  := objectMemory popRemappableOop.
  	methodArg := objectMemory popRemappableOop.
  	primRcvr := objectMemory popRemappableOop.
  	argumentArray := objectMemory popRemappableOop.
  	self successful ifFalse: "If primitive failed, then restore state for failure code"
  		[self pop: arraySize + 1.
  		 self push: ctxtRcvr.
  		 self push: methodArg.
  		 self push: primRcvr.
  		 self push: argumentArray.
  		 argumentCount := 3.
  		 "Hack.  A nil prim error code (primErrorCode = 1) is interpreted by the image
  		  as meaning this primitive is not implemented.  So to pass back nil as an error
  		  code we use -1 to indicate generic failure."
  		 primFailCode = 1 ifTrue:
  			[primFailCode := -1]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveExternalCall (in category 'plugin primitives') -----
  primitiveExternalCall
  	"Call an external primitive. External primitive methods first literals are an array of
  		* The module name (String | Symbol)
  		* The function name (String | Symbol)
  		* The session ID (SmallInteger) [OBSOLETE] (or in Spur, the accessorDepth)
  		* The function index (Integer) in the externalPrimitiveTable
  	For fast interpreter dispatch in subsequent invocations the primitiveFunctionPointer
  	in the method cache is rewritten, either to the function itself, or to zero if the external
  	function is not found.   This allows for fast responses as long as the method stays in
  	the cache. The cache rewrite relies on lastMethodCacheProbeWrite which is set in
  	addNewMethodToCache:.
  	Now that the VM flushes function addresses from its tables, the session ID is obsolete,
  	but it is kept for backward compatibility. Also, a failed lookup is reported specially. If a
  	method has been  looked up and not been found, the function address is stored as -1
  	(i.e., the SmallInteger -1 to distinguish from 16rFFFFFFFF which may be returned from
  	lookup), and the primitive fails with PrimErrNotFound."
  	| lit addr moduleName functionName moduleLength functionLength accessorDepth index |
  	<var: #addr declareC: 'void (*addr)()'>
  	
  	"Fetch the first literal of the method"
+ 	(objectMemory literalCountOf: newMethod) > 0 ifFalse:
- 	(self literalCountOf: newMethod) > 0 ifFalse:
  		[^self primitiveFailFor: PrimErrBadMethod].
  
  	lit := self literal: 0 ofMethod: newMethod. 
  	"Check if it's an array of length 4"
  	((objectMemory isArray: lit) and: [(objectMemory lengthOf: lit) = 4]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadMethod].
  
  	"Look at the function index in case it has been loaded before"
  	index := objectMemory fetchPointer: 3 ofObject: lit.
  	(objectMemory isIntegerObject: index) ifFalse:
  		[^self primitiveFailFor: PrimErrBadMethod].
  	index := objectMemory integerValueOf: index.
  	"Check if we have already looked up the function and failed."
  	index < 0 ifTrue:
  		["Function address was not found in this session, 
  		  Void the primitive function."
  		 self rewriteMethodCacheEntryForExternalPrimitiveToFunction: 0.
  		 ^self primitiveFailFor: PrimErrNotFound].
  
  	"Try to call the function directly"
  	(index > 0 and: [index <= MaxExternalPrimitiveTableSize]) ifTrue:
  		[addr := externalPrimitiveTable at: index - 1.
  		 addr ~= 0 ifTrue:
  			[self rewriteMethodCacheEntryForExternalPrimitiveToFunction: (self cCode: 'addr' inSmalltalk: [1000 + index]).
  			 self callExternalPrimitive: addr.
  			 ^nil].
  		"if we get here, then an index to the external prim was 
  		kept on the ST side although the underlying prim 
  		table was already flushed"
  		^self primitiveFailFor: PrimErrNamedInternal].
  
  	"Clean up session id and external primitive index"
  	objectMemory storePointerUnchecked: 2 ofObject: lit withValue: ConstZero.
  	objectMemory storePointerUnchecked: 3 ofObject: lit withValue: ConstZero.
  
  	"The function has not been loaded yet. Fetch module and function name."
  	moduleName := objectMemory fetchPointer: 0 ofObject: lit.
  	moduleName = objectMemory nilObject
  		ifTrue: [moduleLength := 0]
  		ifFalse: [(objectMemory isBytes: moduleName) ifFalse:
  					[self primitiveFailFor: PrimErrBadMethod].
  				moduleLength := objectMemory lengthOf: moduleName].
  	functionName := objectMemory fetchPointer: 1 ofObject: lit.
  	(objectMemory isBytes: functionName) ifFalse:
  		[self primitiveFailFor: PrimErrBadMethod].
  	functionLength := objectMemory lengthOf: functionName.
  
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[addr := self ioLoadExternalFunction: functionName + BaseHeaderSize
  						OfLength: functionLength
  						FromModule: moduleName + BaseHeaderSize
  						OfLength: moduleLength
  						AccessorDepthInto: (self addressOf: accessorDepth
  												 put: [:val| accessorDepth := val]).
  			 addr = 0
  				ifTrue: [index := -1]
  				ifFalse: "add the function to the external primitive table"
  					[index := self addToExternalPrimitiveTable: addr.
  					 objectMemory
  						storePointerUnchecked: 2
  						ofObject: lit
  						withValue: (objectMemory integerObjectOf: accessorDepth)]]
  		ifFalse:
  			[addr := self ioLoadExternalFunction: functionName + BaseHeaderSize
  						OfLength: functionLength
  						FromModule: moduleName + BaseHeaderSize
  						OfLength: moduleLength.
  			 addr = 0
  				ifTrue: [index := -1]
  				ifFalse: "add the function to the external primitive table"
  					[index := self addToExternalPrimitiveTable: addr]].
  
  	"Store the index (or -1 if failure) back in the literal"
  	objectMemory storePointerUnchecked: 3 ofObject: lit withValue: (objectMemory integerObjectOf: index).
  
  	"If the function has been successfully loaded cache and call it"
  	index >= 0
  		ifTrue:
  			[self rewriteMethodCacheEntryForExternalPrimitiveToFunction: (self cCode: [addr] inSmalltalk: [1000 + index]).
  			 self callExternalPrimitive: addr]
  		ifFalse: "Otherwise void the primitive function and fail"
  			[self rewriteMethodCacheEntryForExternalPrimitiveToFunction: 0.
  			 self assert: (objectMemory fetchPointer: 2 ofObject: lit) = ConstZero.
  			 self primitiveFailFor: PrimErrNotFound]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveObjectPointsTo (in category 'object access primitives') -----
  primitiveObjectPointsTo
  	"This primitive is assumed to be fast (see e.g. MethodDictionary>>includesKey:) so make it so.
+ 	 N.B.  Works forrectly for cogged methods too."
- 	 N.B.  Written to use literalHeaderOf: so that in Cog subclasses cogged methods (whose headers
- 	 point to the machine code method) are still correctly scanned, for the header as well as literals."
  	| rcvr thang header fmt numSlots methodHeader |
  	thang := self stackTop.
  	rcvr := self stackValue: 1.
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self pop: 2 thenPushBool: false].
  
  	"Inlined version of lastPointerOf: for speed in determining if rcvr is a context."
  	header := objectMemory baseHeader: rcvr.
  	fmt := objectMemory formatOfHeader: header.
  	(objectMemory isPointersFormat: fmt)
  		ifTrue:
  			[(fmt = objectMemory indexablePointersFormat
  			  and: [objectMemory isContextHeader: header]) 
  				ifTrue:
  	 				[(self isMarriedOrWidowedContext: rcvr) ifTrue:
  						[self externalWriteBackHeadFramePointers.
  						 (self isStillMarriedContext: rcvr) ifTrue:
  							[^self pop: 2
  									thenPushBool: (self marriedContext: rcvr
  														pointsTo: thang
  														stackDeltaForCurrentFrame: 2)]].
  					"contexts end at the stack pointer"
  					numSlots := CtxtTempFrameStart + (self fetchStackPointerOf: rcvr)]
  				ifFalse:
  					[numSlots := objectMemory numSlotsOf: rcvr]]
  		ifFalse:
  			[fmt < objectMemory firstCompiledMethodFormat "no pointers" ifTrue:
  				[^self pop: 2 thenPushBool: false].
  			"CompiledMethod: contains both pointers and bytes:"
+ 			methodHeader := objectMemory methodHeaderOf: rcvr.
- 			methodHeader := self headerOf: rcvr.
  			methodHeader = thang ifTrue: [^self pop: 2 thenPushBool: true].
+ 			numSlots := (objectMemory literalCountOfMethodHeader: methodHeader) + LiteralStart].
- 			numSlots := (self literalCountOfHeader: methodHeader) + 1].
  
  	self assert: numSlots - 1 * BytesPerOop + objectMemory baseHeaderSize = (objectMemory lastPointerOf: rcvr).
  	objectMemory baseHeaderSize
  		to: numSlots - 1 * BytesPerOop + objectMemory baseHeaderSize
  		by: BytesPerOop
  		do: [:i|
  			(self longAt: rcvr + i) = thang ifTrue:
  				[^self pop: 2 thenPushBool: true]].
  	self pop: 2 thenPushBool: false!

Item was changed:
  ----- Method: StackInterpreterSimulator>>createActualMessageTo: (in category 'debugging traps') -----
  createActualMessageTo: class
+ 	objectMemory bootstrapping ifTrue:
+ 		[self halt].
- 
  	"false
  		ifTrue:
  			[(self stringOf: messageSelector) = 'run:with:in:' ifTrue:
  				[self halt]]
  		ifFalse:
  			[self halt: (self stringOf: messageSelector)]."
  
  	^super createActualMessageTo: class!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:.
  	NSSendIsPCAnnotated := true. "IsNSSendCall used by PushImplicitReceiver"
+ 	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(3 126 126 genDynamicSuperSendBytecode isMapped)			"Newspeak"
  		(2 127 127 genPushImplicitReceiverBytecode isMapped hasIRC)	"Newspeak"
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
  		(2 139 139 genPushExplicitOuterReceiverBytecode isMapped)	"Newspeak"
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForNewspeakV4 (in category 'class initialization') -----
  initializeBytecodeTableForNewspeakV4
  	"StackToRegisterMappingCogit initializeBytecodeTableForNewspeakV4"
  
  	numPushNilsFunction := #v4:Num:Push:Nils:.
  	pushNilSizeFunction := #v4PushNilSize:.
  	NSSendIsPCAnnotated := false. "IsNSSendCall used by SendAbsentImplicit"
+ 	FirstSpecialSelector := 80.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  		(1  77   77 genExtPushPseudoVariableOrOuterBytecode)
  		(1  78   78 genPushConstantZeroBytecode needsFrameNever: 1)
  		(1  79   79 genPushConstantOneBytecode needsFrameNever: 1)
  
  		(1   80   80 genSpecialSelectorArithmetic isMapped AddRR)
  		(1   81   81 genSpecialSelectorArithmetic isMapped SubRR)
  		(1   82   82 genSpecialSelectorComparison isMapped JumpLess)
  		(1   83   83 genSpecialSelectorComparison isMapped JumpGreater)
  		(1   84   84 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1   85   85 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1   86   86 genSpecialSelectorComparison isMapped JumpZero)
  		(1   87   87 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1   88   93 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1   94   94 genSpecialSelectorArithmetic isMapped AndRR)
  		(1   95   95 genSpecialSelectorArithmetic isMapped OrRR)
  		(1   96 101 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 102 102 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 103 103 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 104 111 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 112 127 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 128 143 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 144 159 genSendLiteralSelector2ArgsBytecode isMapped)
  		(1 160 175	genSendAbsentImplicit0ArgsBytecode isMapped hasIRC)
  
  		(1 176 183 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 184 191 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 192 199 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 200 207 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 208 215 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		(1 216 216 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 217 217 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 218 218 genExtReturnTopFromBlock	return needsFrameNever: -1)
  
  		(1 219 219 duplicateTopBytecode			needsFrameNever: 1)
  		(1 220 220 genPopStackBytecode			needsFrameNever: -1)
  		(1 221 221 genExtNopBytecode			needsFrameNever: 0)
  		(1 222 223	unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension					needsFrameNever: 0)
  		(2 225 225 extBBytecode extension					needsFrameNever: 0)
  		(2 226 226 genExtPushReceiverVariableBytecode)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 230 230 genLongPushTemporaryVariableBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtStoreReceiverVariableBytecode)
  		(2 233 233 genExtStoreLiteralVariableBytecode)
  		(2 234 234 genLongStoreTemporaryVariableBytecode)
  		(2 235 235 genExtStoreAndPopReceiverVariableBytecode)
  		(2 236 236 genExtStoreAndPopLiteralVariableBytecode)
  		(2 237 237 genLongStoreAndPopTemporaryVariableBytecode)
  
  		(2 238 238 genExtSendBytecode isMapped)
  		(2 239 239 genExtSendSuperBytecode isMapped)
  		(2 240 240 genExtSendAbsentImplicitBytecode isMapped hasIRC)
  		(2 241 241 genExtSendAbsentDynamicSuperBytecode isMapped)
  
  		(2 242 242 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 243 243 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 244 244 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		(2 245 248	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 249 249 callPrimitiveBytecode)
  		(3 250 250 genPushRemoteTempLongBytecode)
  		(3 251 251 genStoreRemoteTempLongBytecode)
  		(3 252 252 genStoreAndPopRemoteTempLongBytecode)
  		(3 253 253 genExtPushClosureBytecode block v4:Block:Code:Size:)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  	"StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
  
  	numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  	pushNilSizeFunction := #sistaV1PushNilSize:.
+ 	FirstSpecialSelector := 96.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		"1 byte bytecodes"
  		"pushes"
  		(1    0   15 genPushReceiverVariableBytecode			needsFrameNever: 1)
  		(1  16   31 genPushLiteralVariable16CasesBytecode	needsFrameNever: 1)
  		(1  32   63 genPushLiteralConstantBytecode			needsFrameNever: 1)
  		(1  64   75 genPushTemporaryVariableBytecode		needsFrameIfMod16GENumArgs: 1)
  		(1  76   76 genPushReceiverBytecode					needsFrameNever: 1)
  		(1  77   77 genPushConstantTrueBytecode				needsFrameNever: 1)
  		(1  78   78 genPushConstantFalseBytecode			needsFrameNever: 1)
  		(1  79   79 genPushConstantNilBytecode				needsFrameNever: 1)
  		(1  80   80 genPushConstantZeroBytecode				needsFrameNever: 1)
  		(1  81   81 genPushConstantOneBytecode				needsFrameNever: 1)
  		(1  82   82 genExtPushPseudoVariable)
  		(1  83   83 duplicateTopBytecode						needsFrameNever: 1)
  
  		(1  84   87 unknownBytecode)
  
  		"returns"
  		(1  88   88 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  89   89 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  90   90 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  91   91 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1  92   92 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1  93   93 genReturnNilFromBlock			return needsFrameNever: -1)
  		(1  94   94 genReturnTopFromBlock		return needsFrameNever: -1)
  		(1  95   95 genExtNopBytecode			needsFrameNever: 0)
  
  		"sends"
  		(1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  		(1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  		(1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  		(1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  		(1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 104 109 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 120 127 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  
  		(1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
  
  		"jumps"
  		(1 176 183 genShortUnconditionalJump	branch v3:ShortForward:Branch:Distance:)
  		(1 184 191 genShortJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  		(1 192 199 genShortJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean"
  													v3:ShortForward:Branch:Distance:)
  
  		"stores"
  		(1 200 207 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 208 215 genStoreAndPopTemporaryVariableBytecode)
  
  		(1 216 216 genPopStackBytecode needsFrameNever: -1)
  
  		(1 217 223 unknownBytecode)
  
  		"2 byte bytecodes"
  		(2 224 224 extABytecode extension)
  		(2 225 225 extBBytecode extension)
  
  		"pushes"
  		(2 226 226 genExtPushReceiverVariableBytecode		needsFrameNever: 1)
  		(2 227 227 genExtPushLiteralVariableBytecode		needsFrameNever: 1)
  		(2 228 228 genExtPushLiteralBytecode					needsFrameNever: 1)
  		(2 229 229 genLongPushTemporaryVariableBytecode)
  		(2 230 230 genPushClosureTempsBytecode)
  		(2 231 231 genPushNewArrayBytecode)
  		(2 232 232 genExtPushIntegerBytecode				needsFrameNever: 1)
  		(2 233 233 genExtPushCharacterBytecode				needsFrameNever: 1)
  
  		"returns"
  		"sends"
  		(2 234 234 genExtSendBytecode isMapped)
  		(2 235 235 genExtSendSuperBytecode isMapped)
  
  		"sista bytecodes"
  		(2 236 236 genExtTrapIfNotInstanceOfBehaviorsBytecode isMapped)
  
  		"jumps"
  		(2 237 237 genExtUnconditionalJump	branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  		(2 238 238 genExtJumpIfTrue			branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  		(2 239 239 genExtJumpIfFalse			branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  
  		"stores"
  		(2 240 240 genExtStoreAndPopReceiverVariableBytecode)
  		(2 241 241 genExtStoreAndPopLiteralVariableBytecode)
  		(2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  		(2 243 243 genExtStoreReceiverVariableBytecode)
  		(2 244 244 genExtStoreLiteralVariableBytecode)
  		(2 245 245 genLongStoreTemporaryVariableBytecode)
  
  		(2 246 247	unknownBytecode)
  
  		"3 byte bytecodes"
  		(3 248 248 genCallPrimitiveBytecode)
  		(3 249 249 unknownBytecode) "reserved for Push Float"
  		(3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  		(3 251 251 genPushRemoteTempLongBytecode)
  		(3 252 252 genStoreRemoteTempLongBytecode)
  		(3 253 253 genStoreAndPopRemoteTempLongBytecode)
  
  		(3 254 255	unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'class initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackToRegisterMappingCogit initializeBytecodeTableForSqueakV3PlusClosures"
  
  	numPushNilsFunction := #v3:Num:Push:Nils:.
  	pushNilSizeFunction := #v3PushNilSize:.
+ 	FirstSpecialSelector := 176.
  	self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  	self generatorTableFrom: #(
  		(1    0   15 genPushReceiverVariableBytecode needsFrameNever: 1)
  		(1  16   31 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  		(1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  		(1  64   95 genPushLiteralVariableBytecode needsFrameNever: 1)
  		(1  96 103 genStoreAndPopReceiverVariableBytecode needsFrameNever: -1) "N.B. not frameless if immutability"
  		(1 104 111 genStoreAndPopTemporaryVariableBytecode)
  		(1 112 112 genPushReceiverBytecode needsFrameNever: 1)
  		(1 113 113 genPushConstantTrueBytecode needsFrameNever: 1)
  		(1 114 114 genPushConstantFalseBytecode needsFrameNever: 1)
  		(1 115 115 genPushConstantNilBytecode needsFrameNever: 1)
  		(1 116 119 genPushQuickIntegerConstantBytecode needsFrameNever: 1)
  		"method returns in blocks need a frame because of nonlocalReturn:through:"
  		(1 120 120 genReturnReceiver				return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 121 121 genReturnTrue					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 122 122 genReturnFalse					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 123 123 genReturnNil					return needsFrameIfInBlock: isMappedInBlock 0)
  		(1 124 124 genReturnTopFromMethod		return needsFrameIfInBlock: isMappedInBlock -1)
  		(1 125 125 genReturnTopFromBlock		return needsFrameNever: -1)
  
  		(1 126 127 unknownBytecode)
  
  		(2 128 128 extendedPushBytecode needsFrameNever: 1)
  		(2 129 129 extendedStoreBytecode)
  		(2 130 130 extendedStoreAndPopBytecode)
  		(2 131 131 genExtendedSendBytecode isMapped)
  		(3 132 132 doubleExtendedDoAnythingBytecode isMapped)
  		(2 133 133 genExtendedSuperBytecode isMapped)
  		(2 134 134 genSecondExtendedSendBytecode isMapped)
  		(1 135 135 genPopStackBytecode needsFrameNever: -1)
  		(1 136 136 duplicateTopBytecode needsFrameNever: 1)
  
  		(1 137 137 genPushActiveContextBytecode)
  		(2 138 138 genPushNewArrayBytecode)
  
  		(1 139 139 unknownBytecode)
  
  		(3 140 140 genPushRemoteTempLongBytecode)
  		(3 141 141 genStoreRemoteTempLongBytecode)
  		(3 142 142 genStoreAndPopRemoteTempLongBytecode)
  		(4 143 143 genPushClosureCopyCopiedValuesBytecode block v3:Block:Code:Size:)
  
  		(1 144 151 genShortUnconditionalJump			branch v3:ShortForward:Branch:Distance:)
  		(1 152 159 genShortJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:ShortForward:Branch:Distance:)
  		(2 160 163 genLongUnconditionalBackwardJump	branch isMapped "because of interrupt check"
  															v3:Long:Branch:Distance:)
  		(2 164 167 genLongUnconditionalForwardJump		branch v3:Long:Branch:Distance:)
  		(2 168 171 genLongJumpIfTrue					branch isBranchTrue isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  		(2 172 175 genLongJumpIfFalse					branch isBranchFalse isMapped "because of mustBeBoolean"
  															v3:LongForward:Branch:Distance:)
  
  		(1 176 176 genSpecialSelectorArithmetic isMapped AddRR)
  		(1 177 177 genSpecialSelectorArithmetic isMapped SubRR)
  		(1 178 178 genSpecialSelectorComparison isMapped JumpLess)
  		(1 179 179 genSpecialSelectorComparison isMapped JumpGreater)
  		(1 180 180 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  		(1 181 181 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  		(1 182 182 genSpecialSelectorComparison isMapped JumpZero)
  		(1 183 183 genSpecialSelectorComparison isMapped JumpNonZero)
  		(1 184 189 genSpecialSelectorSend isMapped)	 " #* #/ #\\ #@ #bitShift: //"
  		(1 190 190 genSpecialSelectorArithmetic isMapped AndRR)
  		(1 191 191 genSpecialSelectorArithmetic isMapped OrRR)
  		(1 192 197 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  		(1 198 198 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  		(1 199 199 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  		(1 200 207 genSpecialSelectorSend isMapped) "#blockCopy: #value #value: #do: #new #new: #x #y"
  		(1 208 223 genSendLiteralSelector0ArgsBytecode isMapped)
  		(1 224 239 genSendLiteralSelector1ArgBytecode isMapped)
  		(1 240 255 genSendLiteralSelector2ArgsBytecode isMapped))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>availableRegister (in category 'simulation stack') -----
  availableRegister
+ 	| reg |
+ 	reg := self availableRegisterOrNil.
+ 	reg ifNil: [self error: 'no available register'].
+ 	^reg!
- 	| liveRegs |
- 	liveRegs := self liveRegisters.
- 	(liveRegs anyMask: (self registerMaskFor: Arg0Reg)) ifFalse:
- 		[^Arg0Reg].
- 	(liveRegs anyMask: (self registerMaskFor: Arg1Reg)) ifFalse:
- 		[^Arg1Reg].
- 	(liveRegs anyMask: (self registerMaskFor: ClassReg)) ifFalse:
- 		[^ClassReg].
- 	(liveRegs anyMask: (self registerMaskFor: ReceiverResultReg)) ifFalse:
- 		[^ReceiverResultReg].
- 	(liveRegs anyMask: (self registerMaskFor: SendNumArgsReg)) ifFalse:
- 		[^SendNumArgsReg].
- 	self error: 'no available register'.
- 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>availableRegisterOrNil (in category 'simulation stack') -----
  availableRegisterOrNil
+ 	^backEnd availableRegisterOrNilFor: self liveRegisters!
- 	<returnTypeC: #sqInt>
- 	| liveRegs |
- 	liveRegs := self liveRegisters.
- 	(liveRegs anyMask: (self registerMaskFor: Arg1Reg)) ifFalse:
- 		[^Arg1Reg].
- 	(liveRegs anyMask: (self registerMaskFor: Arg0Reg)) ifFalse:
- 		[^Arg0Reg].
- 	(liveRegs anyMask: (self registerMaskFor: SendNumArgsReg)) ifFalse:
- 		[^SendNumArgsReg].
- 	(liveRegs anyMask: (self registerMaskFor: ClassReg)) ifFalse:
- 		[^ClassReg].
- 	(liveRegs anyMask: (self registerMaskFor: ReceiverResultReg)) ifFalse:
- 		[^ReceiverResultReg].
- 	^nil!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genBinaryVarOpVarInlinePrimitive: (in category 'bytecode generators') -----
+ genBinaryVarOpVarInlinePrimitive: prim
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	| ra rr |
+ 	rr := (backEnd availableRegisterOrNilFor: self liveRegisters) ifNil:
+ 			[self ssAllocateRequiredReg:
+ 				(optStatus isReceiverResultRegLive
+ 					ifTrue: [Arg0Reg]
+ 					ifFalse: [ReceiverResultReg])].
+ 	ra := (backEnd availableRegisterOrNilFor: (self liveRegisters bitOr: (self registerMaskFor: rr))) ifNil:
+ 			[self ssAllocateRequiredReg: Arg1Reg].
+ 	(rr = ReceiverResultReg or: [ra = ReceiverResultReg]) ifTrue:
+ 		[optStatus isReceiverResultRegLive: false].
+ 	self ssTop popToReg: ra.
+ 	self ssPop: 1.
+ 	self ssTop popToReg: rr.
+ 	self ssPop: 1.
+ 	prim caseOf: {
+ 		"0 through 6, +, -, *, /, //, \\, quo:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 		[0]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: ra.
+ 				 self AddR: ra R: rr].
+ 		[1]	->	[self SubR: ra R: rr.
+ 				 objectRepresentation genAddSmallIntegerTagsTo: rr].
+ 		[2]	->	[objectRepresentation genRemoveSmallIntegerTagsInScratchReg: rr.
+ 				 objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ra.
+ 				 self MulR: ra R: rr.
+ 				 objectRepresentation genAddSmallIntegerTagsTo: rr].
+ 
+ 		"16 through 19, bitAnd:, bitOr:, bitXor, bitShift:, SmallInteger op SmallInteger => SmallInteger, no overflow"
+ 
+ 		"32	through 37, >, <, >=, <=. =, ~=, SmallInteger op SmallInteger => Boolean (flags?? then in jump bytecodes if ssTop is a flags value, just generate the instruction!!!!)"
+ 
+ 		"64	through 68, Pointer Object>>at:, Byte Object>>at:, Short16 Word Object>>at: LongWord32 Object>>at: Quad64Word Object>>at:. obj op 0-rel SmallInteger => oop"
+ 
+ 		"80	through 84, Pointer Object>>at:put:, Byte Object>>at:put:, Short16 Word Object>>at:put: LongWord32 Object>>at:put: Quad64Word Object>>at:put:. obj op 0-rel SmallInteger => oop"
+ 
+ 	}
+ 	otherwise: [^EncounteredUnknownBytecode].
+ 	self ssPushRegister: rr.
+ 	^0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genCallPrimitiveBytecode (in category 'bytecode generators') -----
+ genCallPrimitiveBytecode
+ 	"SistaV1: 248		11111000 	iiiiiiii		mjjjjjjj		Call Primitive #iiiiiiii + (jjjjjjj * 256) m=1 means inlined primitive, no hard return after execution.
+ 	 See EncoderForSistaV1's class comment and StackInterpreter>>#inlinePrimitiveBytecode:"
+ 	| prim |
+ 	byte2 < 128 ifTrue:
+ 		[^EncounteredUnknownBytecode].
+ 	prim := byte2 - 128 << 8 + byte1.
+ 
+ 	prim < 80 ifTrue:
+ 		[self ssTop type = SSConstant ifTrue:
+ 			[^self genBinaryVarOpConstInlinePrimitive: prim].
+ 		 (self ssValue: 1) type = SSConstant ifTrue:
+ 			[^self genBinaryConstOpVarInlinePrimitive: prim].
+ 		 ^self genBinaryVarOpVarInlinePrimitive: prim].
+ 
+ 	prim < 100 ifTrue:
+ 		[^self genTrinaryInlinePrimitive: prim].
+ 
+ 	^EncounteredUnknownBytecode!

Item was changed:
  ----- Method: VMClass>>deny: (in category 'simulation support') -----
  deny: aBooleanOrBlock
  	<doNotGenerate>
+ 	aBooleanOrBlock value ifTrue: [AssertionFailure signal: 'Assertion failed']!
- 	self assert: aBooleanOrBlock value not!

Item was changed:
  ----- Method: VMCompiledMethodProxy>>header (in category 'literals') -----
  header
+ 	^objectMemory integerValueOf: (objectMemory methodHeaderOf: oop)!
- 	^objectMemory integerValueOf: (coInterpreter headerOf: oop)!

Item was changed:
  ----- Method: VMCompiledMethodProxy>>numLiterals (in category 'accessing') -----
  numLiterals
  	"Answer the number of literals used by the receiver."
  	
+ 	^objectMemory literalCountOf: oop!
- 	^coInterpreter literalCountOf: oop!



More information about the Vm-dev mailing list