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

commits at source.squeak.org commits at source.squeak.org
Fri Oct 4 21:28:29 UTC 2013


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

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

Name: VMMaker.oscog-eem.436
Author: eem
Time: 4 October 2013, 2:25:44.28 pm
UUID: 224a0465-0692-4fb7-afd4-3e247f01bca5
Ancestors: VMMaker.oscog-eem.435

Put num operands of an AbstractInstruction in NumOperands class
var, to ease changing if adding scaled indexed addressing.

Frivolously remove some double period statement separators..

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

Item was changed:
  ----- Method: CoInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: becomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache probe,
  	 since notionally objects' internals are accessed only via sending messages to them (the exception
+ 	 is primitives that access the internals of the non-receiver argument(s).
- 	 is primitives that access the internals of the non-receiver argument(s)..
  	 To avoid a read barrier on bytecode, literal and inst var fetch we scan the receivers and methods
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than scanning all
  	 of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #'char *'>
  
  	(becomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP oop offset |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP.
  					 theSP := theSP + BytesPerWord].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
  			  offset := theFP + (self frameStackedReceiverOffset: theFP).
  			  oop := stackPages longAt: offset.
  			  ((objectMemory isNonImmediate: oop)
  			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: offset
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			 (self isMachineCodeFrame: theFP)
  				ifTrue:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 ((objectMemory isNonImmediate: oop)
  					  and: [(objectMemory isForwarded: oop)]) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 self assert: (objectMemory isForwarded: (self frameMethodObject: theFP)) not]
  				ifFalse:
  					[oop := stackPages longAt: theFP + FoxIFReceiver.
  					 ((objectMemory isNonImmediate: oop)
  					  and: [(objectMemory isForwarded: oop)]) ifTrue:
  						[stackPages
  							longAt: theFP + FoxIFReceiver
  							put: (objectMemory followForwarded: oop)].
  					 oop := self frameMethod: theFP.
  					 (objectMemory isForwarded: oop) ifTrue:
  						[| delta |
  						 delta := (objectMemory followForwarded: oop) - oop.
  						 (theIPPtr ~= 0
  						  and: [(stackPages longAt: theIPPtr) > (self frameMethod: theFP)]) ifTrue:
  							[stackPages
  								longAt: theIPPtr
  								put: (stackPages longAt: theIPPtr) + delta].
  						stackPages
  							longAt: theFP + FoxIFSavedIP
  							put: (stackPages longAt: theFP + FoxIFSavedIP) + delta.
  						stackPages
  							longAt: theFP + FoxMethod
  							put: (objectMemory followForwarded: oop)]].
  			  self followNecessaryForwardingInMethod: (self frameMethod: theFP).
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := theFP + FoxCallerSavedIP.
  				 theFP := callerFP]]]!

Item was changed:
  ----- Method: CoInterpreterMT>>ownVM: (in category 'vm scheduling') -----
  ownVM: threadIndexAndFlags
  	<api>
  	<inline: false>
  	"This is the entry-point for plugins and primitives that wish to reacquire the VM after having
  	 released it via disownVM or callbacks that want to acquire it without knowing their ownership
  	 status.  This call will block until the VM is owned by the current thread or an error occurs.
  	 The argument should be the value answered by disownVM, or 0 for callbacks that don't know
  	 if they have disowned or not.  This is both an optimization to avoid having to query thread-
  	 local storage for the current thread's index (since it can easily keep it in some local variable),
  	 and a record of when an unbound process becomes affined to a thread for the dynamic
  	 extent of some operation.
  
  	 Answer 0 if the current thread is known to the VM.
  	 Answer 1 if the current thread is unknown to the VM and takes ownership.
  	 Answer -1 if the current thread is unknown to the VM and fails to take ownership."
  	| threadIndex flags vmThread myProc activeProc sched |
  	<var: #vmThread type: #'CogVMThread *'>
  	threadIndexAndFlags = 0 ifTrue:
  		[^self ownVMFromUnidentifiedThread].
  	threadIndex := threadIndexAndFlags bitAnd: ThreadIdMask.
  	flags := threadIndexAndFlags >> DisownFlagsShift.
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[relinquishing := false.
  		 self sqLowLevelMFence].
  	(threadIndexAndFlags anyMask: LockGUIThreadFlag) ifTrue:
  		[self assert: (noThreadingOfGUIThread and: [self inGUIThread]).
  		 self assert: disowningVMThread = nil.
  		 (flags anyMask: DisownVMLockOutFullGC) ifTrue:
  			[objectMemory decrementFullGCLock].
  		 cogit recordEventTrace ifTrue:
  			[self recordTrace: TraceOwnVM thing: ConstZero source: 0].
  		 ^0].
  
  	vmThread := cogThreadManager acquireVMFor: threadIndex.
  	disownCount := disownCount - 1.
  
  	(flags anyMask: DisownVMLockOutFullGC) ifTrue:
  		[objectMemory decrementFullGCLock].
  	disowningVMThread notNil ifTrue:
  		[vmThread = disowningVMThread ifTrue:
  			[self cCode: ''
  				inSmalltalk:
  					[| range |
  					 range := self cStackRangeForThreadIndex: threadIndex.
  					 self assert: (range includes: cogit getCStackPointer).
  					 self assert: (range includes: cogit getCFramePointer)].
  			 self assert: self successful.
  			 self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  			 disowningVMThread := nil.
  			 cogit recordEventTrace ifTrue:
  				[self recordTrace: TraceOwnVM thing: ConstOne source: 0].
  			 ^0].  "if not preempted we're done."
  		self preemptDisowningThread].
  	"We've been preempted; we must restore state and update the threadId
  	 in our process, and may have to put the active process to sleep."
  	activeProc := self activeProcess.
  	(threadIndexAndFlags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			[self assert: foreignCallbackProcessSlot == ForeignCallbackProcess.
  			 myProc := objectMemory splObj: foreignCallbackProcessSlot.
  			self assert: myProc ~= objectMemory nilObject.
  			objectMemory splObj: foreignCallbackProcessSlot put: objectMemory nilObject]
  		ifFalse: [myProc := cogThreadManager popAWOLProcess: vmThread].
  	self assert: activeProc ~= myProc.
  	(activeProc ~= objectMemory nilObject
  	 and: [(objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject]) ifTrue:
  		[self putToSleep: activeProc yieldingIf: preemptionYields].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: myProc) = (objectMemory splObj: ProcessInExternalCodeTag).
  	sched := self schedulerPointer.
  	objectMemory
  		storePointer: ActiveProcessIndex ofObject: sched withValue: myProc;
  		storePointerUnchecked: MyListIndex ofObject: myProc withValue: objectMemory nilObject.
  	"Only unaffine if the process was affined at this level and did not become bound in the interim."
  	((threadIndexAndFlags anyMask: ProcessUnaffinedOnDisown)
  	 and: [(self isBoundProcess: myProc) not]) ifTrue:
  		[self setOwnerIndexOfProcess: myProc to: 0 bind: false].
  	self initPrimCall.
  	self externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
  	"If this primitive is called from machine code maintain the invariant that the return pc
  	 of an interpreter callee calling a machine code caller is ceReturnToInterpreterPC."
  	(vmThread inMachineCode
  	 and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	newMethod := vmThread newMethodOrNull.
  	argumentCount := vmThread argumentCount.
  	self cCode:
  			[self mem: reenterInterpreter
  				cp: vmThread reenterInterpreter
  				y: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[reenterInterpreter := vmThread reenterInterpreter].
  	vmThread newMethodOrNull: nil.
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: threadIndex.
  			 self assert: (range includes: vmThread cStackPointer).
  			 self assert: (range includes: vmThread cFramePointer)].
  	cogit setCStackPointer: vmThread cStackPointer.
  	cogit setCFramePointer: vmThread cFramePointer.
+ 	self assert: newMethod ~~ nil.
- 	self assert: newMethod ~~ nil..
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceOwnVM thing: ConstTwo source: 0].
  	^threadIndexAndFlags bitAnd: OwnVMForeignThreadFlag!

Item was changed:
  VMStructType subclass: #CogAbstractInstruction
  	instanceVariableNames: 'opcode machineCodeSize maxSize machineCode operands address dependent cogit objectMemory bcpc'
+ 	classVariableNames: 'NumOperands'
- 	classVariableNames: ''
  	poolDictionaries: 'CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !CogAbstractInstruction commentStamp: 'eem 7/17/2012 15:04' prior: 0!
  I am an abstract instruction generated by the Cogit.  I am subsequently concretized to machine code for the current processor.  A sequence of concretized CogAbstractInstructions are concatenated to form the code for a CogMethod.  I am an abstract class.  My concrete subclasses concretize to the machine code of a specific processor.!

Item was added:
+ ----- Method: CogAbstractInstruction class>>initialize (in category 'class initialization') -----
+ initialize
+ 	NumOperands := 3!

Item was changed:
  ----- Method: CogAbstractInstruction class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in an AbstractInstruction struct."
  	"{CogAbstractInstruction. CogIA32Compiler. CogARMCompiler} do:
  		[:c| Transcript print: c; cr. c printTypedefOn: Transcript]"
  	| machineCodeBytes |
  	machineCodeBytes := self ==  CogAbstractInstruction
  								ifTrue: [0]
  								ifFalse: [self basicNew machineCodeBytes].
  	(self filteredInstVarNames copyWithout: 'machineCode'), #('machineCode') do:
  		[:ivn|
  		ivn ~= 'bcpc' ifTrue:
  			[aBinaryBlock
  				value: ivn
  				value: (ivn caseOf: {
  							['address']			-> ['unsigned long'].
  							['machineCode']	-> [{'unsigned char'. '[', machineCodeBytes printString, ']'}].
+ 							['operands']		-> [{'unsigned long'. '[', NumOperands, ']'}].
- 							['operands']		-> [#('unsigned long' '[3]')].
  							['dependent']		-> ['struct _AbstractInstruction *']}
  						otherwise:
  							[#char])]]!

Item was changed:
  ----- Method: CogAbstractInstruction>>initialize (in category 'initialization') -----
  initialize
  	"This method intializes the Smalltalk instance.  The C instance is merely a struct and doesn't need initialization."
  	<doNotGenerate>
+ 	operands := CArrayAccessor on: (Array new: NumOperands).
- 	operands := CArrayAccessor on: (Array new: 3).
  	machineCode := CArrayAccessor on: (ByteArray new: self machineCodeBytes)!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetClassObjectOfClassIndex:into:scratchReg: (in category 'compile abstract instructions') -----
  genGetClassObjectOfClassIndex: instReg into: destReg scratchReg: scratchReg
  	"Fetch the class object whose index is in instReg into destReg.
  	 It is non-obvious, but the Cogit assumes loading a class does not involve
  	 a runtime call, so do not call classAtIndex:"
  	self assert: instReg ~= destReg.
  	self assert: instReg ~= scratchReg.
  	self assert: destReg ~= scratchReg.
  	cogit
  		MoveR: instReg R: scratchReg;
  		LogicalShiftRightCq: objectMemory classTableMajorIndexShift R: scratchReg;
+ 		LogicalShiftLeftCq: objectMemory shiftForWord R: scratchReg.
- 		LogicalShiftLeftCq: objectMemory shiftForWord R: scratchReg..
  	self assert: (self shouldAnnotateObjectReference: objectMemory classTableRootObj) not.
  	cogit
  		MoveMw: objectMemory classTableRootObj + objectMemory baseHeaderSize r: scratchReg R: destReg;
  		MoveR: instReg R: scratchReg;
  		AndCq: objectMemory classTableMinorIndexMask R: scratchReg;
  		AddCq: objectMemory baseHeaderSize >> objectMemory shiftForWord R: scratchReg;
  		MoveXwr: scratchReg R: destReg R: destReg..
  	^0!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM64rRd MoveMbrR MoveMwrR MoveRAw MoveRM16r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM64rRd MoveMbrR MoveMwrR MoveRAw MoveRM16r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRXbrR MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveXbrRR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: Cogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
+ 	"Generate the run-time entries for the various method and PIC entry misses and aborts.
- 	"Generate the run-time entries for the various method and PIC entry misses and aborts..
  	 Read the class-side method trampolines for documentation on the various trampolines"
  
  	self subclassResponsibility!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := self cCode: [(self addressOf: hasYoungObj) asInteger]
  							inSmalltalk: [CPluggableAccessor new
  											setObject: nil;
  											atBlock: [:obj :idx| hasYoungObj]
  											atPutBlock: [:obj :idx :val| hasYoungObj := val]].
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
+ 			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
- 			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector)..
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
  									with: cogMethod cmUsesPenultimateLit
  									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 "For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  							  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  							 "Only reset the method object's header if it is referring to this CogMethod."
  							 (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  								ifTrue:
  									[coInterpreter
  										rawHeaderOf: cogMethod methodObject
  										put: cogMethod methodHeader.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod.
  									 coInterpreter
  										rawHeaderOf: remappedMethod
  										put: cogMethod asInteger]
  								ifFalse:
  									[ self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
  													= objectMemory nilObject.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod]].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: (self cppIf: NewspeakVM
  											ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
  											ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[cogMethod cmRefersToYoung ifFalse:
  								[cogMethod cmRefersToYoung: true.
  								 methodZone addToYoungReferrers: cogMethod].
  							hasYoungObj := false]
  						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree.
  		 codeModified := true].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: CroquetPlugin>>primitiveOrthoNormInverseMatrix (in category 'transforms') -----
  primitiveOrthoNormInverseMatrix
  	| srcOop dstOop src dst x y z rx ry rz |
  	<export: true>
  	<var: #src declareC:'float *src'>
  	<var: #dst declareC:'float *dst'>
  	<var: #x declareC:'double x'>
  	<var: #y declareC:'double y'>
  	<var: #z declareC:'double z'>
  	<var: #rx declareC:'double rx'>
  	<var: #ry declareC:'double ry'>
  	<var: #rz declareC:'double rz'>
  
  	interpreterProxy methodArgumentCount = 0
  		ifFalse:[^interpreterProxy primitiveFail].
  	srcOop := interpreterProxy stackObjectValue: 0.
  	interpreterProxy failed ifTrue:[^nil].
  	((interpreterProxy isWords: srcOop) and:[(interpreterProxy slotSizeOf: srcOop) = 16])
  		ifFalse:[^interpreterProxy primitiveFail].
  	dstOop := interpreterProxy clone: srcOop.
  	"reload srcOop in case of GC"
  	srcOop := interpreterProxy stackObjectValue: 0.
  	src := interpreterProxy firstIndexableField: srcOop.
  	dst := interpreterProxy firstIndexableField: dstOop.
  
  	"Transpose upper 3x3 matrix"
  	"dst at: 0 put: (src at: 0)."	dst at: 1 put: (src at: 4). 	dst at: 2 put: (src at: 8). 
  	dst at: 4 put: (src at: 1). 	"dst at: 5 put: (src at: 5)."	dst at: 6 put: (src at: 9). 
  	dst at: 8 put: (src at: 2). 	dst at: 9 put: (src at: 6). 	"dst at: 10 put: (src at: 10)."
  
  	"Compute inverse translation vector"
+ 	x := src at: 3.
- 	x := src at: 3..
  	y := src at: 7.
  	z := src at: 11.
  	rx := (x * (dst at: 0)) + (y * (dst at: 1)) + (z * (dst at: 2)).
  	ry := (x * (dst at: 4)) + (y * (dst at: 5)) + (z * (dst at: 6)).
  	rz := (x * (dst at: 8)) + (y * (dst at: 9)) + (z * (dst at: 10)).
  
  	dst at: 3 put: (self cCoerce: 0.0-rx to: 'float').
  	dst at: 7 put: (self cCoerce: 0.0-ry to: 'float').
  	dst at: 11 put: (self cCoerce: 0.0-rz to: 'float').
  
  	interpreterProxy pop: 1.
  	^interpreterProxy push: dstOop.
  !

Item was changed:
  ----- Method: FilePlugin>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'directory primitives') -----
  makeDirEntryName: entryName size: entryNameSize
  	createDate: createDate modDate: modifiedDate
  	isDir: dirFlag fileSize: fileSize
  
  	| modDateOop createDateOop nameString results stringPtr fileSizeOop |
  	<var: 'entryName' type: 'char *'>
  	<var: 'stringPtr' type:'char *'>
  	<var: 'fileSize' type:'squeakFileOffsetType '>
  
  	"allocate storage for results, remapping newly allocated
  	 oops in case GC happens during allocation"
  	interpreterProxy pushRemappableOop:
  		(interpreterProxy instantiateClass: (interpreterProxy classArray) indexableSize: 5).
  	interpreterProxy pushRemappableOop:
+ 		(interpreterProxy instantiateClass: (interpreterProxy classString) indexableSize: entryNameSize).
- 		(interpreterProxy instantiateClass: (interpreterProxy classString) indexableSize: entryNameSize)..
  	interpreterProxy pushRemappableOop: 
  		(interpreterProxy positive32BitIntegerFor: createDate).
  	interpreterProxy pushRemappableOop: 
  		(interpreterProxy positive32BitIntegerFor: modifiedDate).
  	interpreterProxy pushRemappableOop:
  		(interpreterProxy positive64BitIntegerFor: fileSize).
  
  	fileSizeOop   := interpreterProxy popRemappableOop.
  	modDateOop   := interpreterProxy popRemappableOop.
  	createDateOop := interpreterProxy popRemappableOop.
  	nameString    := interpreterProxy popRemappableOop.
  	results         := interpreterProxy popRemappableOop.
  
  	"copy name into Smalltalk string"
  	stringPtr := interpreterProxy firstIndexableField: nameString.
  	0 to: entryNameSize - 1 do: [ :i |
  		stringPtr at: i put: (entryName at: i).
  	].
  
  	interpreterProxy storePointer: 0 ofObject: results withValue: nameString.
  	interpreterProxy storePointer: 1 ofObject: results withValue: createDateOop.
  	interpreterProxy storePointer: 2 ofObject: results withValue: modDateOop.
  	dirFlag
  		ifTrue: [ interpreterProxy storePointer: 3 ofObject: results withValue: interpreterProxy trueObject ]
  		ifFalse: [ interpreterProxy storePointer: 3 ofObject: results withValue: interpreterProxy falseObject ].
  	interpreterProxy storePointer: 4 ofObject: results withValue: fileSizeOop.
  	^ results!

Item was changed:
  ----- Method: IA32ABIPlugin>>primReturnFromContextThrough (in category 'primitives-callbacks') -----
  primReturnFromContextThrough
  	"Return a result from a callback to the callback's callee.  The primitive
  	 has a signature of either of the forms:
  		result <FFICallbackResult> primReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
  		result <FFICallbackResult> primSignal: aSemaphore <Semaphore> andReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
  			<primitive: 'primReturnFromContextThrough' error: errorCode module: 'IA32ABI'>.
  	 If of the second form answer true if this is not the most recent callback, and signal aSemaphore
  	 if it is, so as to implement LIFO ordering of callbacks."
  	<export: true>
  	<legacy>
  	| mac vmCallbackContext vmCallbackReturnValue isMostRecent |
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	<var: #vmCallbackReturnValue type: #'VMCallbackReturnValue *'>
  	vmCallbackContext := self cCoerceSimple: (interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0))
  								to: #'VMCallbackContext *'.
  	(interpreterProxy failed or: [vmCallbackContext = 0]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
  	(mac := interpreterProxy methodArgumentCount) = 3 ifTrue:
  		[isMostRecent := vmCallbackContext = self getMostRecentCallbackContext.
  		isMostRecent ifFalse:
  			[interpreterProxy methodReturnValue: interpreterProxy trueObject.
  			^nil].
  		(interpreterProxy fetchClassOf: (interpreterProxy stackValue: 2)) = interpreterProxy classSemaphore
  			ifFalse: [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  		[interpreterProxy signalNoResume: (interpreterProxy stackValue: 2)] whileFalse].
  	vmCallbackReturnValue := self cCoerceSimple: (self startOfData: (interpreterProxy stackValue: mac))
+ 									to: #'VMCallbackReturnValue *'.
- 									to: #'VMCallbackReturnValue *'..
  	self cCode: "C needs a typedef for structs to be assigned, but that implies a struct class for just one assignment."
  		[self mem: (self addressOf: vmCallbackContext rvs)
  			cp: (self addressOf: vmCallbackReturnValue crvrvs)
  			y: (self sizeof: vmCallbackContext rvs)]
  		inSmalltalk: [vmCallbackContext rvs: vmCallbackReturnValue crvrvs].
  	(interpreterProxy
  		returnAs: (interpreterProxy integerObjectOf: vmCallbackReturnValue type + 1)
  		ThroughCallback: vmCallbackContext
  		Context: (interpreterProxy stackValue: 1)) ifFalse:
  			[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	"NOTREACHED"!

Item was changed:
  ----- Method: InterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'file primitives') -----
  makeDirEntryName: entryName size: entryNameSize
  	createDate: createDate modDate: modifiedDate
  	isDir: dirFlag fileSize: fileSize
  
  	| modDateOop createDateOop nameString results |
  	<var: 'entryName' type: 'char *'>
  
  	"allocate storage for results, remapping newly allocated
  	 oops in case GC happens during allocation"
  	self pushRemappableOop:
  		(self instantiateClass: (self splObj: ClassArray) indexableSize: 5).
  	self pushRemappableOop:
+ 		(self instantiateClass: (self splObj: ClassByteString) indexableSize: entryNameSize).
- 		(self instantiateClass: (self splObj: ClassByteString) indexableSize: entryNameSize)..
  	self pushRemappableOop: (self positive32BitIntegerFor: createDate).
  	self pushRemappableOop: (self positive32BitIntegerFor: modifiedDate).
  
  	modDateOop   := self popRemappableOop.
  	createDateOop := self popRemappableOop.
  	nameString    := self popRemappableOop.
  	results         := self popRemappableOop.
  
  	1 to: entryNameSize do: [ :i |
  		self storeByte: i-1 ofObject: nameString withValue: (entryName at: i) asciiValue.
  	].
  
  	self storePointer: 0 ofObject: results withValue: nameString.
  	self storePointer: 1 ofObject: results withValue: createDateOop.
  	self storePointer: 2 ofObject: results withValue: modDateOop.
  	dirFlag
  		ifTrue: [ self storePointer: 3 ofObject: results withValue: trueObj ]
  		ifFalse: [ self storePointer: 3 ofObject: results withValue: falseObj ].
  	self storePointer: 4 ofObject: results
  		withValue: (self integerObjectOf: fileSize).
  	^ results
  !

Item was changed:
  ----- Method: NewspeakInterpreter>>primitiveByteArrayNByteIIntegerAtPut (in category 'array and stream primitive support') -----
  primitiveByteArrayNByteIIntegerAtPut
  	"Store a (signed or unsigned) n byte integer at the given byte offset."
  	| isSigned byteSize byteOffset rcvr addr value max valueOop |
  	<export: true>
  	<inline: false>
  	isSigned := self booleanValueOf: (self stackValue: 0).
  	byteSize := self stackIntegerValue: 1.
  	valueOop := self stackValue: 2.
  	byteOffset := self stackIntegerValue: 3.
  	self failed ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	rcvr := self stackObjectValue: 4.
  	self failed ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
  	(byteOffset > 0 and:[byteSize = 1 or:[byteSize = 2 or:[byteSize = 4]]])
  		ifFalse:[^self primitiveFailFor: PrimErrBadArgument].
  	addr := self addressOf: rcvr startingAt: byteOffset size: byteSize.
  	self failed ifTrue:[^0].
  	isSigned 
  		ifTrue:[value := self signed32BitValueOf: valueOop]
  		ifFalse:[value := self positive32BitValueOf: valueOop].
  	self failed ifTrue:[^0].
  	byteSize < 4
  		ifTrue:
  			[isSigned ifTrue:[
  				max := 1 << (8 * byteSize - 1).
  				value >= max ifTrue:[^self primitiveFail].
  				value < (0 - max) ifTrue:[^self primitiveFail].
  			] ifFalse:[
  				value >= (1 << (8*byteSize)) ifTrue:[^self primitiveFail].
  			].
  			(self isOopImmutable: rcvr) ifTrue:
+ 				[^self primitiveFailFor: PrimErrNoModification].
- 				[^self primitiveFailFor: PrimErrNoModification]..
  			"short/byte"
  			byteSize = 1 
  				ifTrue:[self byteAt: addr put: value]
  				ifFalse:[	self cCode: '*((short int *) addr) = value' 
  							inSmalltalk: [self shortAt: addr put: value]]]
  		ifFalse:
  			[(self isOopImmutable: rcvr) ifTrue:
  				[^self primitiveFailFor: PrimErrNoModification].
  			self longAt: addr put: value].
  	self pop: 5.
  	^self push: valueOop.!

Item was changed:
  ----- Method: NewspeakInterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'file primitives') -----
  makeDirEntryName: entryName size: entryNameSize
  	createDate: createDate modDate: modifiedDate
  	isDir: dirFlag fileSize: fileSize
  
  	| modDateOop createDateOop nameString results |
  	<var: 'entryName' type: 'char *'>
  
  	"allocate storage for results, remapping newly allocated
  	 oops in case GC happens during allocation"
  	self pushRemappableOop:
  		(self instantiateClass: (self splObj: ClassArray) indexableSize: 5).
  	self pushRemappableOop:
+ 		(self instantiateClass: (self splObj: ClassByteString) indexableSize: entryNameSize).
- 		(self instantiateClass: (self splObj: ClassByteString) indexableSize: entryNameSize)..
  	self pushRemappableOop: (self positive32BitIntegerFor: createDate).
  	self pushRemappableOop: (self positive32BitIntegerFor: modifiedDate).
  
  	modDateOop   := self popRemappableOop.
  	createDateOop := self popRemappableOop.
  	nameString    := self popRemappableOop.
  	results         := self popRemappableOop.
  
  	1 to: entryNameSize do: [ :i |
  		self storeByte: i-1 ofObject: nameString withValue: (entryName at: i) asciiValue.
  	].
  
  	self storePointer: 0 ofObject: results withValue: nameString.
  	self storePointer: 1 ofObject: results withValue: createDateOop.
  	self storePointer: 2 ofObject: results withValue: modDateOop.
  	dirFlag
  		ifTrue: [ self storePointer: 3 ofObject: results withValue: trueObj ]
  		ifFalse: [ self storePointer: 3 ofObject: results withValue: falseObj ].
  	self storePointer: 4 ofObject: results
  		withValue: (self integerObjectOf: fileSize).
  	^ results
  !

Item was changed:
  ----- Method: NewsqueakIA32ABIPlugin>>primReturnFromContextThrough (in category 'primitives-callbacks') -----
  primReturnFromContextThrough
  	"Return a result from a callback to the callback's callee.  The primitive
  	 has a signature of either of the forms:
  		result <FFICallbackResult> primReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
  		result <FFICallbackResult> primSignal: aSemaphore <Semaphore> andReturnFromContext: callbackContext <MethodContext> through: jmpBuf <Integer>
  			<primitive: 'primReturnFromContextThrough' error: errorCode module: 'IA32ABI'>.
  	 If of the second form answer true if this is not the most recent callback, and signal aSemaphore
  	 if it is, so as to implement LIFO ordering of callbacks."
  	<export: true>
  	<legacy>
  	| mac vmCallbackContext vmCallbackReturnValue isMostRecent |
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	<var: #vmCallbackReturnValue type: #'VMCallbackReturnValue *'>
  	vmCallbackContext := self cCoerceSimple: (interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0))
  								to: #'VMCallbackContext *'.
  	(interpreterProxy failed or: [vmCallbackContext = 0]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  
  	(mac := interpreterProxy methodArgumentCount) = 3 ifTrue:
  		[isMostRecent := vmCallbackContext = self getMostRecentCallbackContext.
  		isMostRecent ifFalse:
  			[interpreterProxy methodReturnValue: interpreterProxy trueObject.
  			^nil].
  		(interpreterProxy fetchClassOf: (interpreterProxy stackValue: 2)) = interpreterProxy classSemaphore
  			ifFalse: [^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  		[interpreterProxy signalNoResume: (interpreterProxy stackValue: 2)] whileFalse].
  	vmCallbackReturnValue := self cCoerceSimple: (self startOfData: (interpreterProxy stackValue: mac))
+ 									to: #'VMCallbackReturnValue *'.
- 									to: #'VMCallbackReturnValue *'..
  	self cCode: "C needs a typedef for structs to be assigned, but that implies a struct class for just one assignment."
  		[self mem: (self addressOf: vmCallbackContext rvs)
  			cp: (self addressOf: vmCallbackReturnValue crvrvs)
  			y: (self sizeof: vmCallbackContext rvs)]
  		inSmalltalk: [vmCallbackContext rvs: vmCallbackReturnValue crvrvs].
  	(interpreterProxy
  		returnAs: (interpreterProxy integerObjectOf: vmCallbackReturnValue type + 1)
  		ThroughCallback: vmCallbackContext
  		Context: (interpreterProxy stackValue: 1)) ifFalse:
  			[^interpreterProxy primitiveFailFor: PrimErrBadArgument].
  	"NOTREACHED"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveClass (in category 'primitive generators') -----
  genPrimitiveClass
  	"Stack looks like
  		receiver (also in ReceiverResultReg)
  		return address"
  	(objectRepresentation
  			genGetClassObjectOf: ReceiverResultReg
  			into: ReceiverResultReg
  			scratchReg: TempReg
  			instRegIsReceiver: methodOrBlockNumArgs = 0) = BadRegisterSet ifTrue:
  		[objectRepresentation
  			genGetClassObjectOf: ReceiverResultReg
  			into: ClassReg
  			scratchReg: TempReg
  			instRegIsReceiver: methodOrBlockNumArgs = 0.
+ 		 self MoveR: ClassReg R: ReceiverResultReg].
- 		 self MoveR: ClassReg R: ReceiverResultReg]..
  	self flag: 'currently caller pushes result'.
  	self RetN: BytesPerWord.
  	^0!

Item was changed:
  ----- Method: SpurGenerationScavenger>>fireEphemeronsOnEphemeronList (in category 'weakness and ephemerality') -----
  fireEphemeronsOnEphemeronList
  	"There are ephemerons to be fired in the remembered set.
  	 Fire them and scavenge their keys.  Be careful since copyAndForward:
  	 can remember ephemerons (ephemerons pointing to ephemerons)."
  	| ephemeron ephemeronCorpse |
  	ephemeronList ifNil:
  		[^self].
  	ephemeronCorpse := self firstCorpse: ephemeronList.
  	"Reset the list head so that new ephemerons will get added
  	 to a new list, not concatenated on the one we are scanning."
  	ephemeronList := nil.
  	[ephemeronCorpse notNil] whileTrue:
  		[self assert: (manager isForwarded: ephemeronCorpse).
  		 ephemeron := manager followForwarded: ephemeronCorpse.
+ 		 self assert: (self isScavengeSurvivor: (manager keyOfEphemeron: ephemeron)) not.
- 		 self assert: (self isScavengeSurvivor: (manager keyOfEphemeron: ephemeron)) not..
  		 coInterpreter fireEphemeron: ephemeron.
  		 self copyAndForward: (manager keyOfEphemeron: ephemeron).
  		 self cCoerceSimple: (self scavengeReferentsOf: ephemeron) to: #void.
  		 ephemeronCorpse := self nextCorpseOrNil: ephemeronCorpse]!

Item was changed:
  ----- Method: SpurMemoryManager>>initialInstanceOf: (in category 'object enumeration') -----
  initialInstanceOf: classObj
  	<inline: false>
  	| classIndex |
  	classIndex := self rawHashBitsOf: classObj.
  	classIndex = 0 ifTrue:
  		[^nil].
  	"flush instances in newSpace to settle the enumeration."
+ 	self flushNewSpaceInstancesOf: classObj.
- 	self flushNewSpaceInstancesOf: classObj..
  	self allObjectsDo:
  		[:objOop|
  		classIndex = (self classIndexOf: objOop) ifTrue:
  			[^objOop]].
  	^nil!

Item was changed:
  ----- Method: StackInterpreter>>externalSetStackPageAndPointersForSuspendedContextOfProcess: (in category 'frame access') -----
  externalSetStackPageAndPointersForSuspendedContextOfProcess: aProcess
  	"Set stackPage, instructionPointer, framePointer and stackPointer for the suspendedContext of
  	 aProcess, marrying the context if necessary, and niling the suspendedContext slot.  This is used
  	 on process switch to ensure a context has a stack frame and so can continue execution."
  	| newContext theFrame thePage newPage |
  	<var: #theFrame type: #'char *'>
  	<var: #thePage type: #'StackPage *'>
  	<var: #newPage type: #'StackPage *'>
  	
  	newContext := objectMemory fetchPointer: SuspendedContextIndex ofObject: aProcess.
  	self assert: (objectMemory isContext: newContext).
  	(self isMarriedOrWidowedContext: newContext) ifTrue:
  		[self assert: (self checkIsStillMarriedContext: newContext currentFP: framePointer)].
  	objectMemory
  		storePointerUnchecked: SuspendedContextIndex
  		ofObject: aProcess
  		withValue: objectMemory nilObject.
  	(self isStillMarriedContext: newContext)
  		ifTrue:
  			[theFrame := self frameOfMarriedContext: newContext.
  			 thePage := stackPages stackPageFor: theFrame.
  			 theFrame ~= thePage headFP ifTrue:
  				["explicit assignment of suspendedContext can cause switch to interior frame."
  				 newPage := self newStackPage.
  				 self moveFramesIn: thePage
  					through: (self findFrameAbove: theFrame inPage: thePage)
  					toPage: newPage.
  				  stackPages markStackPageLeastMostRecentlyUsed: newPage].
  			 self assert: thePage headFP = theFrame]
  		ifFalse:
  			[thePage := self makeBaseFrameFor: newContext.
  			 theFrame := thePage baseFP].
  	self setStackPageAndLimit: thePage.
  	stackPointer := thePage headSP.
  	framePointer := thePage headFP.
  	(self isMachineCodeFrame: framePointer) ifFalse:
+ 		[self setMethod: (self iframeMethod: framePointer)].
- 		[self setMethod: (self iframeMethod: framePointer)]..
  	instructionPointer := self popStack.
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer!

Item was changed:
  ----- Method: StackInterpreter>>followForwardingPointersInStackZone: (in category 'object memory support') -----
  followForwardingPointersInStackZone: becomeEffectsFlags
  	"Spur's become: is lazy, turning the becommed object into a forwarding object to the other.
  	 The read-barrier is minimised by arranging that forwarding pointers will fail a method cache probe,
  	 since notionally objects' internals are accessed only via sending messages to them (the exception
+ 	 is primitives that access the internals of the non-receiver argument(s).
- 	 is primitives that access the internals of the non-receiver argument(s)..
  	 To avoid a read barrier on bytecode, literal and inst var fetch we scan the receivers and methods
  	 in the stack zone and follow any forwarded ones.  This is of course way cheaper than scanning all
  	 of memory as in the old become."
  	| theIPPtr |
  	<inline: false>
  	<var: #thePage type: #'StackPage *'>
  	<var: #theSP type: #'char *'>
  	<var: #theFP type: #'char *'>
  	<var: #callerFP type: #'char *'>
  	<var: #theIPPtr type: #'char *'>
  
  	(becomeEffectsFlags anyMask: BecameCompiledMethodFlag) ifTrue:
  		[(objectMemory isForwarded: method) ifTrue:
  			[theIPPtr := instructionPointer - method.
  			 method := objectMemory followForwarded: method.
  			 instructionPointer := method + theIPPtr].
  		(objectMemory isForwarded: newMethod) ifTrue:
  			[newMethod := objectMemory followForwarded: newMethod]].
  
  	self assert: stackPage ~= 0.
  	0 to: numStackPages - 1 do:
  		[:i| | thePage theSP theFP callerFP theIP oop |
  		thePage := stackPages stackPageAt: i.
  		thePage isFree ifFalse:
  			[theSP := thePage headSP.
  			 theFP := thePage  headFP.
  			 "Skip the instruction pointer on top of stack of inactive pages."
  			 thePage = stackPage
  				ifTrue: [theIPPtr := 0]
  				ifFalse:
  					[theIPPtr := theSP.
  					 theSP := theSP + BytesPerWord].
  			 [self assert: (thePage addressIsInPage: theFP).
  			  self assert: (theIPPtr = 0 or: [thePage addressIsInPage: theIPPtr]).
  			  oop := stackPages longAt: theFP + FoxReceiver.
  			  ((objectMemory isNonImmediate: oop)
  			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxReceiver
  					put: (objectMemory followForwarded: oop)].
  			  theIP := theFP + (self frameStackedReceiverOffset: theFP). "reuse theIP; its just an offset here"
  			  oop := stackPages longAt: theIP.
  			  ((objectMemory isNonImmediate: oop)
  			   and: [(objectMemory isForwarded: oop)]) ifTrue:
  				[stackPages
  					longAt: theIP
  					put: (objectMemory followForwarded: oop)].
  			  ((self frameHasContext: theFP)
  			   and: [(objectMemory isForwarded: (self frameContext: theFP))]) ifTrue:
  				[stackPages
  					longAt: theFP + FoxThisContext
  					put: (objectMemory followForwarded: (self frameContext: theFP))].
  			  oop := self frameMethod: theFP.
  			  (objectMemory isForwarded: oop) ifTrue:
  				[| delta |
  				 theIPPtr ~= 0 ifTrue:
  					[self assert: (stackPages longAt: theIPPtr) > (self frameMethod: theFP).
  					 delta := (objectMemory followForwarded: oop) - oop.
  					 stackPages
  						longAt: theIPPtr
  						put: (stackPages longAt: theIPPtr) + delta].
  				stackPages
  					longAt: theFP + FoxMethod
  					put: (objectMemory followForwarded: oop)].
  			  self followNecessaryForwardingInMethod: (self frameMethod: theFP).
  			  (callerFP := self frameCallerFP: theFP) ~= 0] whileTrue:
  				[theIPPtr := theFP + FoxCallerSavedIP.
  				 theFP := callerFP]]]!

Item was changed:
  ----- Method: StackInterpreter>>printActivationNameForSelector:startClass: (in category 'debug printing') -----
  printActivationNameForSelector: aSelector startClass: startClass
  	| methClass |
  	<inline: false>
  	(objectMemory addressCouldBeObj: startClass)
  		ifTrue:
  			[self findClassForSelector: aSelector
  				lookupClass: startClass
  				do: [:class| methClass := class].
  			(methClass isNil or: [startClass = methClass])
  				ifTrue:
+ 					[self printNameOfClass: methClass count: 5.
- 					[self printNameOfClass: methClass count: 5..
  					 self printChar: $>.
  					 methClass ifNil:
  						[self printStringOf: (objectMemory splObj: SelectorDoesNotUnderstand).
  						 self print: ' ']]
  				ifFalse:
  					[self printNameOfClass: startClass count: 5.
  					 self printChar: $(.
  					 self printNameOfClass: methClass count: 5.
  					 self printChar: $).
  					 self printChar: $>]]
  		ifFalse: [self print: 'INVALID CLASS'].
  	(objectMemory addressCouldBeOop: aSelector)
  		ifTrue:
  			[(objectMemory isBytes: aSelector)
  				ifTrue: [self printStringOf: aSelector]
  				ifFalse: [self printOopShort: aSelector]]
  		ifFalse: [self print: 'INVALID SELECTOR']!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>stackToRegisterMapping (in category 'documentation') -----
  stackToRegisterMapping
  	"Stack to register mapping is enabled via a simulation stack { simStack. simStackPtr, simSpillBase } of
  	 operand descriptors (CogSimStackEntry) which serve
  		- to avoid pushing operands to the actual stack by deferring operand manipulation until an
  		  operand-consuming operation (send, store, run-time call)
  		- to record operand type information for constants to avoid unnecessary type checks (e.g. tag checks)
  		- as a simple register allocator since any live registers are recorded in descriptors on the stack.
  
  	The operand types are
  		SSBaseOffset - a value in memory at an offset relative to some register.  For method receiver args
  						 and temps the base register is  FPReg (in a frameful method).  For indirect temps
  						 the register could be any unassigned register.
  		SSConstant - a method literal, hence a Smalltalk object
  		SSRegister - the result of an expression assigned to a register
  		SSSpill - a value spilled to the actual stack
  	The special descriptor simSelf defines self in the current method, relative to FPReg in frameful
  	 methods and  in a register in frameless methods.
  
  	The register allocator aspect allocates registers by searching for SSBaseOffset and SSRegister
  	 descriptors, computing the set of live registers, and then enumerating to find unused ones.
  	 Simulation stack contents must be spilled to the actual stack
  		- at a send (since at a suspension point the actual stack must be valid),
  		- to make a register available if the code generator needs it
  		- at a control flow join (since the two control flows could compute different stack contents and
  		  we choose to avoid the complexity of saving stack contents to allow merging at join points).
  
  	At a control-flow join we must discard type information for values pushed to the stack in either
  	arm of the control-flow, but need /not/ for items pushed before the control flow diverged.  e.g. in
  		self at: 1 put: (expr ifTrue: [v1] ifFalse: [v2]).
  	the 1 is still valid after the control flow join for (expr ifTrue: [v1] ifFalse: [v2]).  So at a conditional
  	branch we record simStackPtr in the target fixup and only void types between it and the
  	simStackPtr at the join point.  This type voiding operation is called merge:.  For now we simply throw
+ 	away all type info but would like to implement the baove scheme soon.
- 	away all type info but would like to implement the baove scheme soon..
  
  	 We can determine the stack depth at a conditional branch (if), but how do we determine the stack
  	 depth following an unconditional jump (else)?  There are essentially three cases
  		e ifTrue: [u] ifFalse: [v],
  		e ifTrue: [^u] ifFalse: [v],
  		e ifTrue: [u] ifFalse: [^v]
  
  		1		expr
  		2		jumpCond L1
  		3		push
  		4		jump L2
  		5	L1:
  		6		push
  		7	L2:
  
  		1		expr
  		2		jumpCond L1
  		3		ret
  		4	L1:
  		5		push
  
  		1		expr
  		2		jumpCond L1
  		3		push
  		4		jump L2
  		5	L1:
  		6		ret
  		7	L2:
  
  	In the first case we can know the merge base at L2 by propagating the merge base from 4 jump L2, which
  	preceeds the target of 2 jumpCond L1.  i.e. the merge base at 7 L2 is the stack pointer at 4 jump L2, which
  	preceeds the target of 2 jumpCond L1.  So at 2 jumpCond L1 we copy the stack pointer to the merge base
  	at 5 L1, /and/ to the preceeding 4 jump L2, and when we reach 4 jump L2, propagate the merge base to 7 L2.
  
  	 Since we're conscious of JIT performance we restrict the live register search range by maintaining
  	 simSpillBase, which is the index of the unspilled entry furthest from the end of simulation stack.
  	 Only entries from simSpillBase to simStackPtr can contain unspilled, and hence live and volatile
  	 registers (the FPReg is not volatile).
  
  	 We further optimize by maintaining a simple optimization status for register contents.
  	 We record whether ReceiverResultReg contains the receiver or an indirect temp vector
  	 and merge this status at control-flow joins."!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateMissAbortTrampolines (in category 'initialization') -----
  generateMissAbortTrampolines
+ 	"Generate the run-time entries for the various method and PIC entry misses and aborts.
- 	"Generate the run-time entries for the various method and PIC entry misses and aborts..
  	 Read the class-side method trampolines for documentation on the various trampolines"
  
  	"Slang needs these apparently superfluous asSymbol sends."
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		methodAbortTrampolines
  			at: numArgs
  			put: (self genMethodAbortTrampolineFor: numArgs)].
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		picAbortTrampolines
  			at: numArgs
  			put: (self genPICAbortTrampolineFor: numArgs)].
  	0 to: self numRegArgs + 1 do:
  		[:numArgs|
  		picMissTrampolines
  			at: numArgs
  			put: (self genPICMissTrampolineFor: numArgs)].
  	self cCode: '' inSmalltalk:
  		[simulatedTrampolines
  			at: (self simulatedAddressFor: #ceSendFromInLineCacheMiss:)
  			put: #ceSendFromInLineCacheMiss:]!



More information about the Vm-dev mailing list