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

commits at source.squeak.org commits at source.squeak.org
Thu Oct 3 20:52:43 UTC 2013


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

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

Name: VMMaker.oscog-eem.430
Author: eem
Time: 3 October 2013, 1:49:56.719 pm
UUID: 8cc48bd0-58e0-4492-a5ca-84f53f03de37
Ancestors: VMMaker.oscog-eem.429

Add forwarding code to InterpreterPrimitives>>primitive[Not]Identical
and bytecodePrimEquivalent

Fix machine code genPrimitiveIdentityHash failure; failure should
call the interpreter primitive to assign the hash.

Make machine-code double primitives deal with Spur having more
than one immediate type.

More protocol added to CogObjectRepresentationFor[NBit]Spur.

Fix logging in CoInterpreter>>commonSend to use lkupClassTag.

Print a method's primitive if it has one in printCogMethod:.

*Don't* check stack depth in ceTraceLinkedSend:. The call isn't at a
suspension point.

Get CogVMSmulator>>ioRelinquishProcessorForMicroseconds: to
increase byteCount so delays can actually fire when idle process is
running (simulator derives time from byteCount).

Add dumpPrimTraceLog to utilities menus.

Fix checkIfValidObjectRef:pc:cogMethod: to correctly check super
sends (added uncheckedEntryAlignment for completeness).
Send print: to coInterpreter in the validity checking routines
(meaningful when simulating).

Correct Cogit>>sendTrace:'s comment.

Change Spur's variable class instantiation to allocate objects with
more than the max fixed fields worth of slots in old space.  Avoids
clogging up new space with huge bitmap objects.

More is(Non)IntegerObject: => is(Non)Immediate:.
genGetCompactClassIndexNonIntOf: => genGetCompactClassIndexNonImmOf:.

Cogit+Spur bootstrap now genuinely evaluates 3+4 (before it was
interpreting due to 1st-level method lookup cache bug).

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

Item was changed:
  ----- Method: CoInterpreter>>checkLogIntegrity (in category 'object memory support') -----
  checkLogIntegrity
  	"Check the log for leaks.  The trace log is a circular buffer of pairs of entries.
  	 If there is an entry at traceLogIndex - 3 \\ TraceBufferSize it has entries.  If
  	 there is something at traceLogIndex it has wrapped."
  	| limit ok |
  	limit := self safe: traceLogIndex - 3 mod: TraceBufferSize.
  	(traceLog at: limit) = 0 ifTrue: [^true].
  	(traceLog at: traceLogIndex) ~= 0 ifTrue:
  		[limit := TraceBufferSize - 3].
  	ok := true.
  	0 to: limit by: 3 do:
  		[:i| | oop |
  		oop := traceLog at: i.
+ 		(objectMemory isImmediate: oop) ifFalse:
- 		(objectMemory isIntegerObject: oop) ifFalse:
  			[(objectMemory checkOopIntegrity: oop named: 'traceLog' index: i) ifFalse:
  				[ok := false]].
  		oop := traceLog at: i + 1.
+ 		(objectMemory isImmediate: oop) ifFalse:
- 		(objectMemory isIntegerObject: oop) ifFalse:
  			[(objectMemory checkOopIntegrity: oop named: 'traceLog' index: i + 1) ifFalse:
  				[ok := false]]].
  	^ok!

Item was changed:
  ----- Method: CoInterpreter>>commonSend (in category 'message sending') -----
  commonSend
  	"Send a message, starting lookup with the receiver's class."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeNamed: 'commonSend' inCase: #singleExtendedSendBytecode>
  	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
  	cogit recordSendTrace ifTrue:
+ 		[self recordTrace: (objectMemory classForClassTag: lkupClassTag)
+ 			thing: messageSelector
+ 			source: TraceIsFromInterpreter.
- 		[self recordTrace: lkupClass thing: messageSelector source: TraceIsFromInterpreter.
  		cogit printOnTrace ifTrue:
+ 			[self printActivationNameForSelector: messageSelector
+ 				startClass: (objectMemory classForClassTag: lkupClassTag); cr]].
- 			[self printActivationNameForSelector: messageSelector startClass: lkupClass; cr]].
  	self internalFindNewMethod.
  	self internalExecuteNewMethod.
  	self fetchNextBytecode!

Item was changed:
  ----- Method: CoInterpreter>>printCogMethod: (in category 'debug printing') -----
  printCogMethod: cogMethod
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	| address primitive |
- 	| address |
  	self cCode: ''
  		inSmalltalk:
  			[self transcript ensureCr.
  			 cogMethod isInteger ifTrue:
  				[^self printCogMethod: (self cCoerceSimple: cogMethod to: #'CogMethod *')]].
  	address := cogMethod asInteger.
  	self printHex: address;
  		print: ' <-> ';
  		printHex: address + cogMethod blockSize.
  	cogMethod cmType = CMMethod ifTrue:
  		[self print: ': method: ';
+ 			printHex: cogMethod methodObject.
+ 		 primitive := self primitiveIndexOfMethod: cogMethod methodObject
+ 							header: cogMethod methodHeader.
+ 		 primitive ~= 0 ifTrue:
+ 			[self print: ' prim '; printNum: primitive]].
- 			printHex: cogMethod methodObject].
  	cogMethod cmType = CMBlock ifTrue:
  		[self print: ': block home: ';
  			printHex: (self cCoerceSimple: cogMethod to: #'CogBlockMethod *') cmHomeMethod asUnsignedInteger].
  	cogMethod cmType = CMClosedPIC ifTrue:
  		[self print: ': Closed PIC N: ';
  			printHex: cogMethod cPICNumCases].
  	cogMethod cmType = CMOpenPIC ifTrue:
  		[self print: ': Open PIC '].
  	self print: ' selector: ';
  		printHex: cogMethod selector;
  		print: ' ';
  		printStringOf: cogMethod selector;
  		cr!

Item was changed:
  ----- Method: CoInterpreter>>printPrimLogEntryAt: (in category 'debug support') -----
  printPrimLogEntryAt: i
  	<inline: false>
  	| intOrSelector |
  	intOrSelector := primTraceLog at: i.
+ 	(objectMemory isImmediate: intOrSelector)
- 	(objectMemory isIntegerObject: intOrSelector)
  		ifTrue:
  			[ intOrSelector = TraceIncrementalGC ifTrue:
  				[self print: '**IncrementalGC**'. ^nil].
  			 intOrSelector = TraceFullGC ifTrue:
  				[self print: '**FullGC**'. ^nil].
  			 intOrSelector = TraceCodeCompaction ifTrue:
  				[self print: '**CompactCode**'. ^nil].
  			 self print: '???']
  		ifFalse:
  			[objectMemory safePrintStringOf: intOrSelector]!

Item was added:
+ ----- Method: CogObjectRepresentation>>smallIntegerIsOnlyImmediateType (in category 'testing') -----
+ smallIntegerIsOnlyImmediateType
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genFetchIndexRegister:from:into: (in category 'compile abstract instructions') -----
+ genFetchIndexRegister: indexReg from: tableObj into: destReg
+ 	"indexReg contains the 1-relative index of an element in tableObj.
+ 	 Since BaseHeaderSize > BytesPerOop we must adjust it to use
+ 	 it as a zero-relative index from the beginning of the object."
+ 	self assert: indexReg ~= destReg.
+ 	cogit AddCq: objectMemory baseHeaderSize / objectMemory wordSize - 1 R: indexReg.
+ 	cogit annotate: (cogit MoveCw: tableObj R: destReg) objRef: tableObj.
+ 	cogit MoveXwr: indexReg R: destReg R: destReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genFetchIndexRegister:from:into: (in category 'compile abstract instructions') -----
+ genFetchIndexRegister: indexReg from: tableObj into: destReg
+ 	"indexReg contains the 1-relative index of an element in tableObj.
+ 	 Since BaseHeaderSize = BytesPerOop we can use it as a
+ 	 zero-relative index from the beginning of the object."
+ 	self assert: indexReg ~= destReg.
+ 	cogit annotate: (cogit MoveCw: tableObj R: destReg) objRef: tableObj.
+ 	cogit MoveXwr: indexReg R: destReg R: destReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genAllocFloatValue:into:scratchReg:scratchReg: (in category 'primitive generators') -----
+ genAllocFloatValue: dpreg into: resultReg scratchReg: scratch1 scratchReg: scratch2
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	| allocSize newFloatHeader jumpFail |
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	allocSize := objectMemory baseHeaderSize + (objectMemory sizeof: #double).
+ 	newFloatHeader := objectMemory
+ 							headerForSlots: (self sizeof: #double) / objectMemory wordSize
+ 							format: objectMemory firstLongFormat
+ 							classIndex: objectMemory classFloatCompactIndex.
+ 	cogit MoveAw: objectMemory freeStartAddress R: resultReg.
+ 	cogit MoveAw: objectMemory scavengeThresholdAddress R: scratch2.
+ 	cogit LoadEffectiveAddressMw: allocSize r: resultReg R: scratch1.
+ 	cogit CmpR: scratch2 R: scratch1.
+ 	jumpFail := cogit JumpAboveOrEqual: 0.
+ 	cogit MoveR: scratch1 Aw: objectMemory freeStartAddress.
+ 	cogit MoveCq: newFloatHeader R: scratch2.
+ 	objectMemory wordSize = objectMemory baseHeaderSize
+ 		ifTrue: [cogit MoveR: scratch2 Mw: 0 r: resultReg]
+ 		ifFalse:
+ 			[self flag: #endianness.
+ 			 cogit MoveCq: 0 R: scratch1.
+ 			 cogit MoveR: scratch2 Mw: 0 r: resultReg.
+ 			 cogit MoveR: scratch1 Mw: objectMemory wordSize r: resultReg.].
+ 	cogit MoveRd: dpreg M64: objectMemory baseHeaderSize r: resultReg.
+ 	^jumpFail!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genFetchIndexRegister:from:into: (in category 'compile abstract instructions') -----
+ genFetchIndexRegister: indexReg from: tableObj into: destReg
+ 	"indexReg contains the 1-relative index of an element in tableObj."
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetClassIndexOfNonImm:into: (in category 'compile abstract instructions') -----
+ genGetClassIndexOfNonImm: sourceReg into: destReg
+ 	"Fetch the instance's class index into destReg."
+ 
+ 	cogit MoveMw: 0 r: sourceReg R: destReg.
+ 	cogit AndCq: objectMemory classIndexMask R: destReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetCompactClassIndexNonImmOf:into: (in category 'compile abstract instructions') -----
+ genGetCompactClassIndexNonImmOf: instReg into: destReg
+ 	"Fetch the instance's class index into destReg."
+ 	^self genGetClassIndexOfNonImm: instReg into: destReg!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genGetDoubleValueOf:into: (in category 'compile abstract instructions') -----
+ genGetDoubleValueOf: srcReg into: destFPReg 
+ 	cogit MoveM64: objectMemory baseHeaderSize r: srcReg Rd: destFPReg.
+ 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>smallIntegerIsOnlyImmediateType (in category 'testing') -----
+ smallIntegerIsOnlyImmediateType
+ 	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genFetchIndexRegister:from:into: (in category 'compile abstract instructions') -----
  genFetchIndexRegister: indexReg from: tableObj into: destReg
+ 	"indexReg contains the 1-relative index of an element in tableObj.
+ 	 Since BaseHeaderSize = BytesPerOop we can use it as a
+ 	 zero-relative index from the beginning of the object."
  	self assert: indexReg ~= destReg.
  	cogit annotate: (cogit MoveCw: tableObj R: destReg) objRef: tableObj.
  	cogit MoveXwr: indexReg R: destReg R: destReg.
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genGetCompactClassIndexNonImmOf:into: (in category 'compile abstract instructions') -----
+ genGetCompactClassIndexNonImmOf: instReg into: destReg
+ 	"Fetch the instance's compact class index into destReg."
+ 	"Get header word in scratchReg"
+ 	cogit MoveMw: 0 r: instReg R: destReg.
+ 	"Form the byte index of the compact class field"
+ 	cogit LogicalShiftRightCq: objectMemory compactClassFieldLSB R: destReg.
+ 	cogit AndCq: self compactClassFieldMask R: destReg.
+ 	^0!

Item was removed:
- ----- Method: CogObjectRepresentationForSqueakV3>>genGetCompactClassIndexNonIntOf:into: (in category 'compile abstract instructions') -----
- genGetCompactClassIndexNonIntOf: instReg into: destReg
- 	"Fetch the instance's compact class index into destReg."
- 	"Get header word in scratchReg"
- 	cogit MoveMw: 0 r: instReg R: destReg.
- 	"Form the byte index of the compact class field"
- 	cogit LogicalShiftRightCq: objectMemory compactClassFieldLSB R: destReg.
- 	cogit AndCq: self compactClassFieldMask R: destReg.
- 	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genJumpImmediateInScratchReg: (in category 'compile abstract instructions') -----
+ genJumpImmediateInScratchReg: aRegister
+ 	^self genJumpSmallIntegerInScratchReg: aRegister!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>smallIntegerIsOnlyImmediateType (in category 'testing') -----
+ smallIntegerIsOnlyImmediateType
+ 	^true!

Item was changed:
  ----- Method: CogVMSimulator>>ceTraceLinkedSend: (in category 'debug support') -----
  ceTraceLinkedSend: theReceiver
- 	| cogMethod delta |
  	(sendCount := sendCount + 1) \\ 500 = 0 ifTrue:
  		[self changed: #byteCountText].
  	cogit printOnTrace ifTrue:
  		[transcript print: byteCount; nextPut: $/; print: sendCount; space].
  	cogit assertCStackWellAligned.
  	super ceTraceLinkedSend: theReceiver.
- 	cogMethod := cogit cogBlockMethodSurrogateAt: (self stackTop - cogit traceLinkedSendOffset).
- 	cogMethod stackCheckOffset > 0 ifTrue:
- 		[delta := (cogMethod cmType = CMMethod
- 				   and: [cogMethod cmNumArgs > cogit numRegArgs])
- 					ifTrue: [cogMethod cmNumArgs + 1]
- 					ifFalse: [0].
- 		 self maybeCheckStackDepth: delta sp: stackPointer + BytesPerWord pc: (stackPages longAt: stackPointer)]. "skip return address for ceTraceLinkedSend call."
  	^#continue!

Item was changed:
  ----- Method: CogVMSimulator>>ioMSecs (in category 'I/O primitives support') -----
  ioMSecs
  	"Return the value of the millisecond clock."
  	"NOT.  Actually, we want something a lot slower and, for exact debugging,
  	something more repeatable than real time.  I have an idea: use the byteCount... (di 7/1/2004 13:55)"
  
+ 	^self microsecondsToMilliseconds: self ioUTCMicroseconds
- 	^self ioUTCMicroseconds // 1000 bitAnd: MillisecondClockMask
  	
  "At 20k bytecodes per second, this gives us about 200 ticks per second, or about 1/5 of what you'd expect for the real time clock.  This should still service events at one or two per second"!

Item was changed:
  ----- Method: CogVMSimulator>>ioRelinquishProcessorForMicroseconds: (in category 'I/O primitives support') -----
  ioRelinquishProcessorForMicroseconds: microseconds
  	"In the simulator give an indication that we're idling and check for input.
+ 	 If called from machine code then increment the byte count since the clock
+ 	 is derived from it and the clock will not advance otherwise.
  	 If we're simulating threading we're in difficulties.  We need a UI process
  	 (to run activities such as fill-in-the-blanks) but we also need an independent
  	 thread of control to run this VM thread.  So we need to fork a new UI process."
  	Display reverse: (0 at 0 extent: 16 at 16).
+ 	instructionPointer >= objectMemory startOfMemory ifFalse:
+ 		[byteCount := byteCount + microseconds - 1.
+ 		 self incrementByteCount].
  	Sensor peekEvent ifNotNil:
  		[self forceInterruptCheck].
  	Processor activeProcess == Project uiProcess ifTrue:
  		[World doOneCycle].
  	microseconds >= 1000
  		ifTrue: [self isThreadedVM ifTrue:
  					[self forceInterruptCheckFromHeartbeat].
  				(Delay forMilliseconds: microseconds + 999 // 1000) wait]
  		ifFalse: [Processor yield]!

Item was added:
+ ----- Method: CogVMSimulator>>primitiveNewWithArg (in category 'debugging traps') -----
+ primitiveNewWithArg
+ 	"(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [self classNameOf: (self stackValue: 1) Is: 'Bitmap']) ifTrue:
+ 		[self printExternalHeadFrame.
+ 		 self halt]."
+ 	^super primitiveNewWithArg!

Item was added:
+ ----- Method: CogVMSimulator>>primitiveSignalAtMilliseconds (in category 'system control primitives') -----
+ primitiveSignalAtMilliseconds
+ 	super primitiveSignalAtMilliseconds.
+ 	self successful ifTrue:
+ 		[Transcript
+ 			cr; nextPutAll: thisContext selector;
+ 			nextPutAll: ' now '; nextPutAll: self ioUTCMicroseconds hex;
+ 			nextPutAll: ' wakeup '; nextPutAll: nextWakeupUsecs hex;
+ 			nextPutAll: ' wakeup - now '; print: self ioUTCMicroseconds - nextWakeupUsecs; flush]!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print all stacks' action: #printAllStacks;
  		addLine;
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action: [cogit disassembleCodeAt: cogit processor pc];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
+ 		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: 'set break pc...' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: bpc]];
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

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 postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall 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 maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
- 	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 postCompileHook primInvokeLabel methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMissCall missOffset entryPointMask checkedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry dynSuperEntry dynSuperEntryAlignment cmDynSuperEntryOffset mnuCall interpretCall 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 maxMethodBefore maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceClosureCopyTrampoline ceCreateNewArrayTrampoline ceEnterCogCodePopReceiverReg ceEnterCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceActiveContextTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline cePositive32BitIntegerTrampoline ceImplicitReceiverTrampoline ceExplicitReceiverTrampoline ceCaptureCStackPointers ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetSP sendTrampolines superSendTrampolines dynamicSuperSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner cogMethodSurrogateClass cogBlockMethodSurrogateClass extA extB'
  	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 NumSendTrampolines NumTrampolines ProcessorClass 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>>checkIfValidObjectRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidObjectRef: annotation pc: mcpc cogMethod: cogMethod
  	<var: #mcpc type: #'char *'>
+ 	<var: #sendTable type: #'sqInt *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation checkValidObjectReference: literal) ifFalse:
+ 			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
- 			[self print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  	(self isSendAnnotation: annotation) ifTrue:
+ 		[| entryPoint selectorOrCacheTag offset sendTable |
- 		[| entryPoint selectorOrCacheTag |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 self
+ 			offsetAndSendTableFor: entryPoint
+ 			annotation: annotation
+ 			into: [:off :table| offset := off. sendTable := table].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
+ 		 (entryPoint > methodZoneBase
+ 		  and: [offset ~= cmNoCheckEntryOffset])
+ 			ifTrue: "linked non-super send, cacheTag is a cacheTag"
- 		 entryPoint > methodZoneBase
- 			ifTrue: "linked send, cacheTag is a cacheTag"
  				[(objectRepresentation checkValidInlineCacheTag: selectorOrCacheTag) ifFalse:
+ 					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
- 					[self print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]
+ 			ifFalse: "unlinked send or super send; cacheTag is a selector"
- 			ifFalse: "unlinked send; cacheTag is a selector"
  				[(objectRepresentation checkValidObjectReference: selectorOrCacheTag) ifFalse:
+ 					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
- 					[self print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>checkIntegrityOfObjectReferencesInCode: (in category 'debugging') -----
  checkIntegrityOfObjectReferencesInCode: fullGCFlag
  	<api>
  	"Answer if all references to objects in machine-code are valid."	
  	| cogMethod ok count |
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	ok := true.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmRefersToYoung ifTrue:
  				[(count := methodZone occurrencesInYoungReferrers: cogMethod) ~= 1 ifTrue:
+ 					[coInterpreter print: 'young referrer CM '; printHex: cogMethod asInteger.
- 					[self print: 'young referrer CM '; printHex: cogMethod asInteger.
  					 count = 0
+ 						ifTrue: [coInterpreter print: ' is not in youngReferrers'; cr]
+ 						ifFalse: [coInterpreter print: ' is in youngReferrers '; printNum: count; print: ' times!!'; cr].
- 						ifTrue: [self print: ' is not in youngReferrers'; cr]
- 						ifFalse: [self print: ' is in youngReferrers '; printNum: count; print: ' times!!'; cr].
  					 ok := false]].
  			 (objectRepresentation checkValidObjectReference: cogMethod selector) ifFalse:
+ 				[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' selector'; cr.
- 				[self print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' selector'; cr.
  				 ok := false].
  			 cogMethod cmType = CMMethod
  				ifTrue:
  					[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  					 (objectRepresentation checkValidObjectReference: cogMethod methodObject) ifFalse:
+ 						[coInterpreter print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' methodObject'; cr.
- 						[self print: 'object leak in CM '; printHex: cogMethod asInteger; print: ' methodObject'; cr.
  						 ok := false].
  					 (self mapFor: cogMethod
  						 performUntil: #checkIfValidObjectRef:pc:cogMethod:
  						 arg: cogMethod asInteger) ~= 0
  							ifTrue: [ok := false].
  					 fullGCFlag ifFalse:
  						[(((objectMemory isYoung: cogMethod methodObject)
  						    or: [objectMemory isYoung: cogMethod selector])
  						   and: [cogMethod cmRefersToYoung not]) ifTrue:
+ 							[coInterpreter print: 'CM '; printHex: cogMethod asInteger; print: ' refers to young but not marked as such'; cr.
- 							[self print: 'CM '; printHex: cogMethod asInteger; print: ' refers to young but not marked as such'; cr.
  							 ok := false]]]
  				ifFalse:
  					[cogMethod cmType = CMClosedPIC
  						ifTrue:
  							[(self checkValidObjectReferencesInClosedPIC: cogMethod) ifFalse:
  								[ok := false]]
  						ifFalse:
  							[cogMethod cmType = CMOpenPIC
  								ifTrue:
  									[(self mapFor: cogMethod
  										performUntil: #checkIfValidObjectRef:pc:cogMethod:
  										arg: cogMethod asInteger) ~= 0
  											ifTrue: [ok := false]]]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	^ok!

Item was changed:
  ----- Method: Cogit>>computeEntryOffsets (in category 'initialization') -----
  computeEntryOffsets
  	"Generate the entry code for a method to determine cmEntryOffset and cmNoCheckEntryOffset.  We
  	 need cmNoCheckEntryOffset up front to be able to generate the map starting from cmNoCheckEntryOffset"
  	"stack allocate the various collections so that they
  	 are effectively garbage collected on return."
  	self allocateOpcodes: 20 bytecodes: 0.
  	methodOrBlockNumArgs := 0.
  	self compileAbort.
  	self compileEntry.
  	self computeMaximumSizes.
  	self generateInstructionsAt: methodZoneBase + (self sizeof: CogMethod).
  	cmEntryOffset := entry address - methodZoneBase.
  	cmNoCheckEntryOffset := noCheckEntry address - methodZoneBase.
  	self cppIf: NewspeakVM
  		ifTrue: [cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase].
  	missOffset := sendMissCall address + sendMissCall machineCodeSize - methodZoneBase.
  	entryPointMask := BytesPerWord - 1.
  	[self cppIf: NewspeakVM
  		ifTrue: [(cmEntryOffset bitAnd: entryPointMask) = (cmNoCheckEntryOffset bitAnd: entryPointMask)
  				or: [(cmEntryOffset bitAnd: entryPointMask) = (cmDynSuperEntryOffset bitAnd: entryPointMask)
  				or: [(cmNoCheckEntryOffset bitAnd: entryPointMask) = (cmDynSuperEntryOffset bitAnd: entryPointMask)]]]
  		ifFalse: [(cmEntryOffset bitAnd: entryPointMask) = (cmNoCheckEntryOffset bitAnd: entryPointMask)]] whileTrue:
  		[entryPointMask := entryPointMask + entryPointMask + 1].
  	entryPointMask >= (methodZone roundUpLength: 1) ifTrue:
  		[self error: 'cannot differentiate checked and unchecked entry-points with current cog method alignment'].
  	checkedEntryAlignment := cmEntryOffset bitAnd: entryPointMask.
+ 	uncheckedEntryAlignment := cmNoCheckEntryOffset bitAnd: entryPointMask.
+ 	self assert: checkedEntryAlignment ~= uncheckedEntryAlignment.
- 	self assert: checkedEntryAlignment ~= (cmNoCheckEntryOffset bitAnd: entryPointMask).
  	self cppIf: NewspeakVM
  		ifTrue:
  			[cmDynSuperEntryOffset := dynSuperEntry address - methodZoneBase.
  			 dynSuperEntryAlignment := cmDynSuperEntryOffset bitAnd: entryPointMask.
+ 			self assert: dynSuperEntryAlignment ~= checkedEntryAlignment.
+ 			self assert: dynSuperEntryAlignment ~= uncheckedEntryAlignment]!
- 			self assert: (cmDynSuperEntryOffset bitAnd: entryPointMask) ~= (cmEntryOffset bitAnd: entryPointMask).
- 			self assert: (cmDynSuperEntryOffset bitAnd: entryPointMask) ~= (cmNoCheckEntryOffset bitAnd: entryPointMask)]!

Item was changed:
  ----- Method: Cogit>>sendTrace: (in category 'debugging') -----
  sendTrace: aBooleanOrInteger
  	<doNotGenerate>
  	"traceFlags is a set of flags.
+ 	 1 => print trace (if something below is selected)
- 	 1 => print trace (if somethigg below is selected)
  	 2 => trace sends
  	 4 => trace block activations
  	 8 => trace interpreter primitives
  	 16 => trace events (context switches, GCs, etc)
+ 	 32 => trace stack overflow
+ 	 64 => send breakpoint on implicit receiver (Newspeak VM only)"
- 	 32 => send breakpoint on implicit receiver (Newspeak VM only)"
  	traceFlags := aBooleanOrInteger isInteger
  							ifTrue: [aBooleanOrInteger]
  							ifFalse: [aBooleanOrInteger ifTrue: [6] ifFalse: [0]]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveIdentical (in category 'object access primitives') -----
  primitiveIdentical
  	"is the receiver/first argument the same object as the (last) argument?.
  	 pop argumentCount because this can be used as a mirror primitive."
  	| thisObject otherObject |
  	otherObject := self stackValue: 1.
  	thisObject := self stackTop.
+ 	(objectMemory isOopForwarded: otherObject) ifTrue:
+ 		[self assert: argumentCount > 1.
+ 		 otherObject := objectMemory followForwarded: thisObject].
+ 	self assert: (objectMemory isOopForwarded: otherObject) not.
+ 	(objectMemory isOopForwarded: thisObject) ifTrue:
+ 		[thisObject := objectMemory followForwarded: thisObject].
  	self pop: argumentCount + 1 thenPushBool: thisObject = otherObject!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNotIdentical (in category 'object access primitives') -----
  primitiveNotIdentical
  	"is the receiver/first argument not the same object as the (last) argument?.
  	 pop argumentCount because this can be used as a mirror primitive."
  	| thisObject otherObject |
  	otherObject := self stackValue: 1.
  	thisObject := self stackTop.
+ 	(objectMemory isOopForwarded: otherObject) ifTrue:
+ 		[self assert: argumentCount > 1.
+ 		 otherObject := objectMemory followForwarded: thisObject].
+ 	(objectMemory isOopForwarded: thisObject) ifTrue:
+ 		[thisObject := objectMemory followForwarded: thisObject].
  	self pop: argumentCount + 1 thenPushBool: thisObject ~= otherObject!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
  	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp fail |
- 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpSmallInt doOp fail |
  	<var: #jumpFailClass type: #'AbstractInstruction *'>
  	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
- 	<var: #jumpSmallInt type: #'AbstractInstruction *'>
  	<var: #jumpFailCheck type: #'AbstractInstruction *'>
  	<var: #doOp type: #'AbstractInstruction *'>
  	<var: #fail type: #'AbstractInstruction *'>
  	self MoveMw: BytesPerWord r: SPReg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: TempReg R: ClassReg.
+ 	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genGetCompactClassIndexNonIntOf: ClassReg into: SendNumArgsReg.
  	self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
  	jumpFailClass := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
  	doOp := self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
  	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
  	jumpFailAlloc := objectRepresentation
  					genAllocFloatValue: DPFPReg0
  					into: SendNumArgsReg
  					scratchReg: ClassReg
  					scratchReg: TempReg.
  	self MoveR: SendNumArgsReg R: ReceiverResultReg.
  	self flag: 'currently caller pushes result'.
  	self RetN: BytesPerWord * 2.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
- 	jumpSmallInt jmpTarget: self Label.
  	objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: ClassReg.
  	self ConvertR: ClassReg Rd: DPFPReg1.
  	self Jump: doOp.
  	jumpFailAlloc jmpTarget: self Label.
  	self compileInterpreterPrimitive: (coInterpreter
  										functionPointerForCompiledMethod: methodObj
  										primitiveIndex: primitiveIndex).
  	fail := self Label.
+ 	jumpFailClass jmpTarget: fail.
- 	jumpFailClass jmpTarget: self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck jmpTarget: fail].
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: fail].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genDoubleComparison:invert: (in category 'primitive generators') -----
  genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
  	"Stack looks like
  		receiver (also in ResultReceiverReg)
  		arg
  		return address"
  	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
+ 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	| jumpFail jumpSmallInt jumpCond compare |
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	<var: #jumpSmallInt type: #'AbstractInstruction *'>
  	<var: #jumpCond type: #'AbstractInstruction *'>
  	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 
  	self MoveMw: BytesPerWord r: SPReg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: TempReg R: ClassReg.
+ 	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
- 	jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genGetCompactClassIndexNonIntOf: ClassReg into: SendNumArgsReg.
  	self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
  	jumpFail := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: ClassReg into: DPFPReg1.
  	invertComparison "May need to invert for NaNs"
  		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
  		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
  	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
  		objRef: objectMemory falseObject.
  	self flag: 'currently caller pushes result'.
  	self RetN: BytesPerWord * 2.
  	jumpCond jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
  							objRef: objectMemory trueObject).
  	self RetN: BytesPerWord * 2.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
- 	jumpSmallInt jmpTarget: self Label.
  	objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: ClassReg.
  	self ConvertR: ClassReg Rd: DPFPReg1.
  	self Jump: compare.
  	jumpFail jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
  genPrimitiveIdentityHash
  	| jumpSI jumpNotSet |
  	<var: #jumpSI type: #'AbstractInstruction *'>
  	<var: #jumpNotSet type: #'AbstractInstruction *'>
  	self MoveR: ReceiverResultReg R: ClassReg.
  	jumpSI := objectRepresentation genJumpSmallIntegerInScratchReg: ClassReg.
  	objectRepresentation genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
  	objectRepresentation isHashSetOnInstanceCreation ifFalse:
  		[self CmpCq: ConstZero R: TempReg.
  		 jumpNotSet := self JumpZero: 0].
  	self MoveR: TempReg R: ReceiverResultReg.
  	self flag: 'currently caller pushes result'.
  	self RetN: BytesPerWord.
- 	jumpSI jmpTarget: self Label.
  	objectRepresentation isHashSetOnInstanceCreation ifFalse:
+ 		[jumpNotSet jmpTarget: self Label.
+ 		 self compileInterpreterPrimitive: (coInterpreter
+ 											functionPointerForCompiledMethod: methodObj
+ 											primitiveIndex: primitiveIndex)].
+ 	jumpSI jmpTarget: self Label.
- 		[jumpNotSet jmpTarget: jumpSI getJmpTarget].
  	^0!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>freeStart: (in category 'cog jit support') -----
+ freeStart: aValue
+ 	^freeStart := aValue!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>freeStartAddress (in category 'trampoline support') -----
+ freeStartAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: freeStart) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #freeStart in: self]!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>scavengeThreshold (in category 'cog jit support') -----
+ scavengeThreshold
+ 	^scavengeThreshold!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager>>scavengeThresholdAddress (in category 'trampoline support') -----
+ scavengeThresholdAddress
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: scavengeThreshold) asUnsignedInteger]
+ 		inSmalltalk: [cogit simulatedReadWriteVariableAddress: #scavengeThreshold in: self]!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements * 2].
  		[self firstLongFormat]	->
  			[numSlots := nElements].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
  		[self firstCompiledMethodFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)] }
  		otherwise: ["some Squeak images include funky fixed subclasses of abstract variable
  					 superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
  					 Allow fixed classes to be instantiated here iff nElements = 0."
  					 (nElements ~= 0 or: [instSpec >= self sixtyFourBitIndexableFormat]) ifTrue:
  						[^nil].
  					 numSlots := self fixedFieldsOfClassFormat: classFormat]. "non-indexable"
  	classIndex := self ensureBehaviorHash: classObj.
  	classIndex < 0 ifTrue:
  		[coInterpreter primitiveFailFor: classIndex negated.
  		 ^nil].
+ 	numSlots > self maxSlotsForNewSpaceAlloc
+ 		ifTrue: [newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
+ 		ifFalse: [newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
- 	newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex.
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>instantiateClass:indexableSize: (in category 'instantiation') -----
  instantiateClass: classObj indexableSize: nElements
  	| instSpec classFormat numSlots classIndex newObj fillValue |
  	classFormat := self formatOfClass: classObj.
  	instSpec := self instSpecOfClassFormat: classFormat.
  	fillValue := 0.
  	instSpec caseOf: {
  		[self arrayFormat]	->
  			[numSlots := nElements.
  			 fillValue := nilObj].
  		[self indexablePointersFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self weakArrayFormat]	->
  			[numSlots := (self fixedFieldsOfClassFormat: classFormat) + nElements.
  			 fillValue := nilObj].
  		[self sixtyFourBitIndexableFormat]	->
  			[numSlots := nElements].
  		[self firstLongFormat]	->
  			[numSlots := nElements + 1 // 2.
  			 instSpec := instSpec + (nElements bitAnd: 1)].
  		[self firstShortFormat]	->
  			[numSlots := nElements + 3 // 4.
  			 instSpec := instSpec + (4 - nElements bitAnd: 3)].
  		[self firstByteFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (8 - nElements bitAnd: 7)].
  		[self firstCompiledMethodFormat]	->
  			[numSlots := nElements + 7 // 8.
  			 instSpec := instSpec + (8 - nElements bitAnd: 7)] }
  		otherwise: ["some Squeak images include funky fixed subclasses of abstract variable
  					 superclasses. e.g. DirectoryEntry as a subclass of ArrayedCollection.
  					 Allow fixed classes to be instantiated here iff nElements = 0."
  					 (nElements ~= 0 or: [instSpec >= self sixtyFourBitIndexableFormat]) ifTrue:
  						[^nil].
  					 numSlots := self fixedFieldsOfClassFormat: classFormat]. "non-indexable"
  	classIndex := self ensureBehaviorHash: classObj.
  	classIndex < 0 ifTrue:
  		[coInterpreter primitiveFailFor: classIndex negated.
  		 ^nil].
+ 	numSlots > self maxSlotsForNewSpaceAlloc
+ 		ifTrue: [newObj := self allocateSlotsInOldSpace: numSlots format: instSpec classIndex: classIndex]
+ 		ifFalse: [newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex].
- 	newObj := self allocateSlots: numSlots format: instSpec classIndex: classIndex.
  	newObj ifNotNil:
  		[self fillObj: newObj numSlots: numSlots with: fillValue].
  	^newObj!

Item was added:
+ ----- Method: SpurMemoryManager>>classFloatCompactIndex (in category 'cog jit support') -----
+ classFloatCompactIndex
+ 	<api>
+ 	^ClassFloatCompactIndex!

Item was changed:
  ----- Method: SpurMemoryManager>>clone: (in category 'allocation') -----
  clone: objOop
  	| numSlots newObj |
  	numSlots := self numSlotsOf: objOop.
+ 	
+ 	numSlots > self maxSlotsForNewSpaceAlloc
+ 		ifTrue:
+ 			[newObj := self allocateSlotsInOldSpace: numSlots
+ 							format: (self formatOf: objOop)
+ 							classIndex: (self classIndexOf: objOop)]
+ 		ifFalse:
+ 			[newObj := self allocateSlots: numSlots
+ 							format: (self formatOf: objOop)
+ 							classIndex: (self classIndexOf: objOop)].
- 	newObj := self allocateSlots: (self numSlotsOf: objOop)
- 					format: (self formatOf: objOop)
- 					classIndex: (self classIndexOf: objOop).
  	(self isPointersNonImm: objOop)
  		ifTrue:
  			[0 to: numSlots - 1 do:
  				[:i| | oop |
  				oop := self fetchPointer: i ofObject: objOop.
  				((self isNonImmediate: oop)
  				 and: [self isForwarded: oop]) ifTrue:
  					[oop := self followForwarded: oop].
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: oop].
  			((self isRemembered: objOop)
  			 and: [(self isYoung: newObj) not]) ifTrue:
  				[scavenger remember: newObj.
  				 self setIsRememberedOf: newObj to: true]]
  		ifFalse:
  			[0 to: numSlots - 1 do:
  				[:i|
  				self storePointerUnchecked: i
  					ofObject: newObj
  					withValue: (self fetchPointer: i ofObject: objOop)]].
  	^newObj!

Item was changed:
  ----- Method: SpurMemoryManager>>freeStart (in category 'accessing') -----
  freeStart
+ 	(#(Cogit SimpleStackBasedCogit StackToregisterMappingCogit) includes: thisContext sender class name) ifTrue:
+ 		[self halt].
  	^freeStart!

Item was added:
+ ----- Method: SpurMemoryManager>>maxSlotsForNewSpaceAlloc (in category 'instantiation') -----
+ maxSlotsForNewSpaceAlloc
+ 	"Almost entirely arbitrary, but we dont want 1Mb bitmaps allocated in eden.
+ 	 But this choice means no check for numSlots > maxSlotsForNewSpaceAlloc
+ 	 for non-variable allocations."
+ 	^self fixedFieldsOfClassFormatMask!

Item was changed:
  ----- Method: SpurMemoryManager>>printHeaderTypeOf: (in category 'debug printing') -----
  printHeaderTypeOf: objOop
  	coInterpreter print: ((self numSlotsOf: objOop) >= self numSlotsMask
+ 							ifTrue: [' 16 byte header']
+ 							ifFalse: [' 8 byte header'])!
- 							ifTrue: [' 8 byte header']
- 							ifFalse: [' 16 byte header'])!

Item was added:
+ ----- Method: SpurMemoryManager>>safePrintStringOf: (in category 'debug printing') -----
+ safePrintStringOf: oop
+ 	| target |
+ 	target := (self isOopForwarded: oop)
+ 				ifTrue: [self followForwarded: oop]
+ 				ifFalse: [oop].
+ 	^coInterpreter printStringOf: target!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimClass (in category 'common selector sends') -----
  bytecodePrimClass
  	| rcvr |
  	rcvr := self internalStackTop.
+ 	(objectMemory isOopForwarded: rcvr) ifTrue:
+ 		[rcvr := self handleSpecialSelectorSendFaultFor: rcvr].
  	self internalStackTopPut: (objectMemory fetchClassOf: rcvr).
  	self fetchNextBytecode!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimEquivalent (in category 'common selector sends') -----
  bytecodePrimEquivalent
- 
  	| rcvr arg |
  	rcvr := self internalStackValue: 1.
+ 	(objectMemory isOopForwarded: rcvr) ifTrue:
+ 		[rcvr := self handleSpecialSelectorSendFaultFor: rcvr].
  	arg := self internalStackValue: 0.
+ 	(objectMemory isOopForwarded: arg) ifTrue:
+ 		[arg := self handleSpecialSelectorSendFaultFor: arg].
+ 	self booleanCheat: rcvr = arg!
- 	self booleanCheat: rcvr = arg.!

Item was changed:
  ----- Method: StackInterpreter>>bytecodePrimEquivalentV4 (in category 'common selector sends') -----
  bytecodePrimEquivalentV4
- 
  	| rcvr arg |
  	rcvr := self internalStackValue: 1.
  	arg := self internalStackValue: 0.
+ 	(objectMemory isOopForwarded: rcvr) ifTrue:
+ 		[rcvr := self handleSpecialSelectorSendFaultFor: rcvr].
+ 	(objectMemory isOopForwarded: arg) ifTrue:
+ 		[arg := self handleSpecialSelectorSendFaultFor: arg].
+ 	self booleanCheatV4: rcvr = arg!
- 	self booleanCheatV4: rcvr = arg.!

Item was changed:
  ----- Method: StackInterpreter>>handleForwardedSendFaultFor: (in category 'message sending') -----
  handleForwardedSendFaultFor: classTag
  	"Handle a send fault that may be due to a send to a forwarded object.
  	 Unforward the receiver on the stack and answer its actual class."
  	| rcvr |
+ 	<inline: false>
+ 	self assert: (objectMemory isForwardedClassTag: classTag).
- 	(objectMemory isForwardedClassTag: classTag) ifFalse:
- 		[^classTag].
  
  	rcvr := self stackValue: argumentCount.
+ 	"should *not* be a super send, so the receiver should be forwarded."
- 	"should *not* be a super send, so te receiver should be forwarded."
  	self assert: (objectMemory isOopForwarded: rcvr).
  	rcvr := objectMemory followForwarded: rcvr.
  	self stackValue: argumentCount put: rcvr.
  	self followForwardedFrameContents: framePointer
  		stackPointer: stackPointer + (argumentCount + 1 * BytesPerWord). "don't repeat effort"
  	(objectMemory isPointers: (self frameReceiver: framePointer)) ifTrue:
  		[objectMemory
  			followForwardedObjectFields: (self frameReceiver: framePointer)
  			toDepth: 0].
  	^objectMemory fetchClassTagOf: rcvr!

Item was added:
+ ----- Method: StackInterpreter>>handleSpecialSelectorSendFaultFor: (in category 'message sending') -----
+ handleSpecialSelectorSendFaultFor: obj
+ 	<inline: true>
+ 	^self handleSpecialSelectorSendFaultFor: obj fp: localFP sp: localSP!

Item was added:
+ ----- Method: StackInterpreter>>handleSpecialSelectorSendFaultFor:fp:sp: (in category 'message sending') -----
+ handleSpecialSelectorSendFaultFor: obj fp: theFP sp: theSP
+ 	"Handle a special send fault that may be due to a special selector
+ 	 send accessing a forwarded object.
+ 	 Unforward the object on the stack and in inst vars and answer its target."
+ 	<inline: false>
+ 	<var: #fp type: #'char *'>
+ 	<var: #sp type: #'char *'>
+ 	self assert: (objectMemory isOopForwarded: obj).
+ 
+ 	self followForwardedFrameContents: theFP stackPointer: theSP.
+ 	(objectMemory isPointers: (self frameReceiver: theFP)) ifTrue:
+ 		[objectMemory
+ 			followForwardedObjectFields: (self frameReceiver: theFP)
+ 			toDepth: 0].
+ 	^objectMemory followForwarded: obj!

Item was changed:
  ----- Method: StackInterpreter>>ioLocalMicroseconds (in category 'primitive support') -----
  ioLocalMicroseconds
  	<doNotGenerate>
+ 	^self ioUTCMicroseconds + (1000000 * DateAndTime localOffset asSeconds)!
- 	^Time localMicrosecondClock!

Item was changed:
  ----- Method: StackInterpreterSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulation;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'short print ext frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'long print ext frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
+ 		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		addLine;
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'inspect cointerpreter' action: #inspect;
  		addLine;
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector'.
  											s notEmpty ifTrue: [self setBreakSelector: s]];
  		add: (printSends
  				ifTrue: ['no print sends']
  				ifFalse: ['print sends'])
  			action: [self ensureDebugAtEachStepBlock.
  					printSends := printSends not];
  		"currently printReturns does nothing"
  		"add: (printReturns
  				ifTrue: ['no print returns']
  				ifFalse: ['print returns'])
  			action: [self ensureDebugAtEachStepBlock.
  					printReturns := printReturns not];"
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleArithmetic:preOpCheck: (in category 'primitive generators') -----
  genDoubleArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
  	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
- 	| jumpFailClass jumpFailAlloc jumpFailCheck jumpSmallInt doOp |
  	<var: #jumpFailClass type: #'AbstractInstruction *'>
  	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	<var: #jumpSmallInt type: #'AbstractInstruction *'>
  	<var: #jumpFailCheck type: #'AbstractInstruction *'>
  	<var: #doOp type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
  	self MoveR: Arg0Reg R: ClassReg.
+ 	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genGetCompactClassIndexNonIntOf: Arg0Reg into: SendNumArgsReg.
  	self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
  	jumpFailClass := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	doOp := self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck := self perform: preOpCheckOrNil with: DPFPReg0 with: DPFPReg1].
  	self gen: arithmeticOperator operand: DPFPReg1 operand: DPFPReg0.
  	jumpFailAlloc := objectRepresentation
  						genAllocFloatValue: DPFPReg0
  						into: SendNumArgsReg
  						scratchReg: ClassReg
  						scratchReg: TempReg.
  	self MoveR: SendNumArgsReg R: ReceiverResultReg.
  	self RetN: 0.
  	"We need to push the register args on two paths; this one and the interpreter primitive path.
  	But the interpreter primitive path won't unless regArgsHaveBeenPushed is false."
  	self assert: methodOrBlockNumArgs <= self numRegArgs.
  	jumpFailClass jmpTarget: self Label.
  	preOpCheckOrNil ifNotNil:
  		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
  	self genPushRegisterArgsForNumArgs: methodOrBlockNumArgs.
  	jumpFailClass := self Jump: 0.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
- 	jumpSmallInt jmpTarget: self Label.
  	objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: ClassReg.
  	self ConvertR: ClassReg Rd: DPFPReg1.
  	self Jump: doOp.
  	jumpFailAlloc jmpTarget: self Label.
  	self compileInterpreterPrimitive: (coInterpreter
  										functionPointerForCompiledMethod: methodObj
  										primitiveIndex: primitiveIndex).
  	jumpFailClass jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genDoubleComparison:invert: (in category 'primitive generators') -----
  genDoubleComparison: jumpOpcodeGenerator invert: invertComparison
  	"Receiver and arg in registers.
  	 Stack looks like
  		return address"
  	<var: #jumpOpcodeGenerator declareC: 'AbstractInstruction *(*jumpOpcodeGenerator)(void *)'>
+ 	| jumpFail jumpImmediate jumpNonInt jumpCond compare |
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
- 	| jumpFail jumpSmallInt jumpCond compare |
- 	<var: #jumpFail type: #'AbstractInstruction *'>
- 	<var: #jumpSmallInt type: #'AbstractInstruction *'>
  	<var: #jumpCond type: #'AbstractInstruction *'>
  	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: TempReg.
  	objectRepresentation genGetDoubleValueOf: ReceiverResultReg into: DPFPReg0.
+ 	jumpImmediate := objectRepresentation genJumpImmediateInScratchReg: TempReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
- 	jumpSmallInt := objectRepresentation genJumpSmallIntegerInScratchReg: TempReg.
- 	objectRepresentation genGetCompactClassIndexNonIntOf: Arg0Reg into: SendNumArgsReg.
  	self CmpCq: objectMemory classFloatCompactIndex R: SendNumArgsReg.
  	jumpFail := self JumpNonZero: 0.
  	objectRepresentation genGetDoubleValueOf: Arg0Reg into: DPFPReg1.
  	invertComparison "May need to invert for NaNs"
  		ifTrue: [compare := self CmpRd: DPFPReg0 Rd: DPFPReg1]
  		ifFalse: [compare := self CmpRd: DPFPReg1 Rd: DPFPReg0].
  	jumpCond := self perform: jumpOpcodeGenerator with: 0. "FP jumps are a little weird"
  	self annotate: (self MoveCw: objectMemory falseObject R: ReceiverResultReg)
  		objRef: objectMemory falseObject.
  	self RetN: 0.
  	jumpCond jmpTarget: (self annotate: (self MoveCw: objectMemory trueObject R: ReceiverResultReg)
  								objRef: objectMemory trueObject).
  	self RetN: 0.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg].
- 	jumpSmallInt jmpTarget: self Label.
  	objectRepresentation genConvertSmallIntegerToIntegerInScratchReg: Arg0Reg.
  	self ConvertR: Arg0Reg Rd: DPFPReg1.
  	self Jump: compare.
  	jumpFail jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveIdentityHash (in category 'primitive generators') -----
  genPrimitiveIdentityHash
  	| jumpSI jumpNotSet |
  	<var: #jumpSI type: #'AbstractInstruction *'>
  	<var: #jumpNotSet type: #'AbstractInstruction *'>
  	self MoveR: ReceiverResultReg R: ClassReg.
  	jumpSI := objectRepresentation genJumpSmallIntegerInScratchReg: ClassReg.
  	objectRepresentation genGetHashFieldNonImmOf: ReceiverResultReg asSmallIntegerInto: TempReg.
  	objectRepresentation isHashSetOnInstanceCreation ifFalse:
  		[self CmpCq: ConstZero R: TempReg.
  		 jumpNotSet := self JumpZero: 0].
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: 0.
- 	jumpSI jmpTarget: self Label.
  	objectRepresentation isHashSetOnInstanceCreation ifFalse:
+ 		[jumpNotSet jmpTarget: self Label.
+ 		 self compileInterpreterPrimitive: (coInterpreter
+ 											functionPointerForCompiledMethod: methodObj
+ 											primitiveIndex: primitiveIndex)].
+ 	jumpSI jmpTarget: self Label.
- 		[jumpNotSet jmpTarget: jumpSI getJmpTarget].
  	^0!



More information about the Vm-dev mailing list