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

commits at source.squeak.org commits at source.squeak.org
Thu Dec 24 14:16:14 UTC 2015


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

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

Name: VMMaker.oscog-eem.1611
Author: eem
Time: 24 December 2015, 2:14:20.511 pm
UUID: 854947cd-58c3-4c34-a8cc-bf673b67983c
Ancestors: VMMaker.oscog-eem.1610

x64 Cogit:
Implement machine code SmallFloat primitives.  Fix conversion bug in maybeGenConvertIfSmallFloatIn:... (fix refactored into genGetSmallFloatValueOf:scratch:into:).

Streamline genJumpNotSmallFloatValueBits:scratch:'s isolation of the exponent.

Slang:
Allow the Cogit's primitive table to reference optional primitives (since SmallFloat prims are <option: #Spur64BitMemoryManager>.

Simulator:
Reimplement the brakpoint machinery in an OO manner, allowing multiple breakpoints and deleting all breakpoints.

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

Item was added:
+ ----- Method: Array>>addBreakpoint: (in category '*VMMaker-interpreter simulator') -----
+ addBreakpoint: address
+ 	^self, {address}!

Item was added:
+ ----- Method: Array>>isActiveBreakpoint (in category '*VMMaker-interpreter simulator') -----
+ isActiveBreakpoint
+ 	^self size > 0!

Item was added:
+ ----- Method: Array>>isBreakpointFor: (in category '*VMMaker-interpreter simulator') -----
+ isBreakpointFor: address
+ 	1 to: self size do:
+ 		[:i| (self at: i) = address ifTrue: [^true]].
+ 	^false!

Item was added:
+ ----- Method: Array>>menuPrompt (in category '*VMMaker-interpreter simulator') -----
+ menuPrompt
+ 	^String streamContents:
+ 		[:s|
+ 		s space; nextPut: $(.
+ 		self do: [:address| s nextPutAll: address hex]
+ 			separatedBy: [s space].
+ 		s nextPut: $)]!

Item was added:
+ ----- Method: Array>>removeBreakpoint: (in category '*VMMaker-interpreter simulator') -----
+ removeBreakpoint: address
+ 	^(self copyWithout: address) ifEmpty: nil!

Item was added:
+ ----- Method: Array>>singleStepRequiredToTriggerIn: (in category '*VMMaker-interpreter simulator') -----
+ singleStepRequiredToTriggerIn: aCogit
+ 	^self anySatisfy: [:address| address between: aCogit cogCodeBase and: aCogit methodZone limitZony]!

Item was added:
+ ----- Method: BlockClosure>>shouldStopIfAtPC: (in category '*VMMaker-interpreter simulator') -----
+ shouldStopIfAtPC: address
+ 	<primitive: 202>
+ 	^self value: address!

Item was added:
+ ----- Method: Boolean>>isBreakpointFor: (in category '*VMMaker-interpreter simulator') -----
+ isBreakpointFor: address
+ 	^self!

Item was added:
+ ----- Method: Boolean>>menuPrompt (in category '*VMMaker-interpreter simulator') -----
+ menuPrompt
+ 	^' (CLICK STEPPING!!!!)'!

Item was added:
+ ----- Method: Boolean>>shouldStopIfAtPC: (in category '*VMMaker-interpreter simulator') -----
+ shouldStopIfAtPC: address
+ 	^self!

Item was added:
+ ----- Method: CogObjectRepresentation class>>wordSize (in category 'accessing') -----
+ wordSize
+ 	^4!

Item was changed:
  ----- Method: CogObjectRepresentationFor32BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
  branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	| jmpImmediate|
  	<inline: true>
- 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	cogit MoveR: reg R: TempReg.
  	classIndex = objectMemory smallIntegerTag ifTrue:
  		[jmpImmediate := self genJumpNotSmallIntegerInScratchReg: TempReg].
  	classIndex = objectMemory characterTag ifTrue:
  		[jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
  	jmpImmediate jmpTarget: targetFixUp!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur class>>wordSize (in category 'accessing') -----
+ wordSize
+ 	^8!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>branchIf:hasNotImmediateTag:target: (in category 'sista support') -----
  branchIf: reg hasNotImmediateTag: classIndex target: targetFixUp
+ 	<var: #targetFixUp type: #'AbstractInstruction *'>
  	| jmpImmediate|
  	<inline: true>
  	cogit MoveR: reg R: TempReg.
  	classIndex = objectMemory smallIntegerTag ifTrue:
  		[jmpImmediate := self genJumpNotSmallIntegerInScratchReg: TempReg].
  	classIndex = objectMemory characterTag ifTrue:
  		[jmpImmediate := self genJumpNotCharacterInScratchReg: TempReg].
  	classIndex = objectMemory smallFloatTag ifTrue:
  		[jmpImmediate := self genJumpNotSmallFloatInScratchReg: TempReg].
  	jmpImmediate jmpTarget: targetFixUp!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genGetSmallFloatValueOf:scratch:into: (in category 'compile abstract instructions') -----
+ genGetSmallFloatValueOf: oopReg scratch: scratch into: dpReg
+ 	"Convert the SmallFloat oop in ooppReg into the corresponding float value in dpReg.
+ 	 c.f. Spur64BitMemoryManager>>smallFloatBitsOf:"
+ 	| jumpSFZero |
+ 	<var: 'jumpSFZero' type: #'AbstractInstruction *'>
+ 	cogit
+ 		MoveR: oopReg R: scratch;
+ 		LogicalShiftRightCq: objectMemory numTagBits R: scratch;
+ 		CmpCq: 1 R: scratch.
+ 	jumpSFZero := cogit JumpLessOrEqual: 0.
+ 	cogit AddCq: objectMemory smallFloatExponentOffset << (objectMemory smallFloatMantissaBits + 1) R: scratch.
+ 	jumpSFZero jmpTarget: (cogit RotateRightCq: 1 R: scratch).
+ 	cogit MoveR: scratch Rd: dpReg.
+ 	^0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallFloatValueBits:scratch: (in category 'compile abstract instructions') -----
  genJumpNotSmallFloatValueBits: reg scratch: exponent
  	"Generate a test to check that the integer register contains a floating point value within the SmallFloat64 range,
  	 and answer the jump.  c.f. Spur64BitMemoryManager>>isSmallFloatValue:"
  	| jumpFail jumpTest jumpMinExponent jumpMaxExponent jumpZeroMantissa |
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	<var: #jumpTest type: #'AbstractInstruction *'>
  	<var: #jumpMinExponent type: #'AbstractInstruction *'>
  	<var: #jumpMaxExponent type: #'AbstractInstruction *'>
  	<var: #jumpZeroMantissa type: #'AbstractInstruction *'>
+ 	self flag: 'if we combine the exponent range test with the conversion to tagged representation we test for a zero exponent only once. further, if we extract tags once into a scratch on the input side we test for immediates, SmallInteger and SmallFloat using the same intermediate result.  so to do is to move fp arithmetic into the object representations'.
+ 	cogit MoveR: reg R: exponent.
+ 	true
+ 		ifTrue: [cogit
+ 				LogicalShiftLeftCq: 1 R: exponent; "drop sign"
+ 				LogicalShiftRightCq: objectMemory smallFloatMantissaBits + 1 R: exponent] "shift exponent down"
+ 		ifFalse: [cogit
+ 				LogicalShiftRightCq: objectMemory smallFloatMantissaBits R: exponent;
+ 				AndCq: 16r7FF R: exponent].  "ieee double precision mantissa is 11 bits"
+ 	cogit CmpCq: objectMemory smallFloatExponentOffset R: exponent.
- 	cogit MoveR: reg R: exponent;
- 		LogicalShiftRightCq: objectMemory smallFloatMantissaBits R: exponent;
- 		AndCq: 16r7FF R: exponent;  "ieee double precision mantissa is 11 bits"
- 		CmpCq: objectMemory smallFloatExponentOffset R: exponent.
  	jumpMinExponent := cogit JumpLessOrEqual: 0.
  	cogit CmpCq: 255 + objectMemory smallFloatExponentOffset R: exponent. "SmallFloat exponent is 8 bits"
  	jumpMaxExponent := cogit JumpLessOrEqual: 0.
  	jumpFail :=
  	cogit Jump: 0.
  	jumpMinExponent jmpTarget:
  	(cogit TstCq: 1 << objectMemory smallFloatMantissaBits - 1 R: reg). "test mantissa bits"
  	jumpZeroMantissa := cogit JumpZero: 0.
  	cogit CmpCq: objectMemory smallFloatExponentOffset R: exponent.
  	jumpTest :=
  	cogit Jump: 0.
  	jumpZeroMantissa jmpTarget:
  	(cogit CmpCq: 0 R: exponent).
  	jumpTest jmpTarget:
  	(cogit JumpNonZero: jumpFail).
  	jumpMaxExponent jmpTarget: cogit Label.
  	^jumpFail!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpNotSmallInteger:scratchReg: (in category 'compile abstract instructions') -----
  genJumpNotSmallInteger: reg scratchReg: scratch
  	"Generate a compare and branch to test if aRegister contains other than a SmallInteger.
  	 Answer the jump.  Override since scratch is needed."
- 	<returnTypeC: #'AbstractInstruction *'>
  	^cogit
  		AndCq: objectMemory tagMask R: reg R: scratch;
  		CmpCq: objectMemory smallIntegerTag R: scratch;
  		JumpNonZero: 0!

Item was changed:
  ----- Method: CogObjectRepresentationFor64BitSpur>>maybeGenConvertIfSmallFloatIn:scratchReg:into:andJumpTo: (in category 'primitive generators') -----
  maybeGenConvertIfSmallFloatIn: oopReg scratchReg: scratch into: dpReg andJumpTo: targetInst
+ 	"Generate a test for a smallFloat in oopReg, converting it to the float value in dpReg
+ 	 and jumping to targetInst. If oopReg does not contain a SmallFloat, fall through."
- 	"Generate a test for a smallFloat in  oopReg, converting it to the float value in dpReg and jumping to targetInst.
- 	 c.f. Spur64BitMemoryManager>>smallFloatBitsOf:"
  	<var: 'targetInst' type: #'AbstractInstruction *'>
+ 	| jumpNotSF |
- 	| jumpNotSF jumpSFZero |
  	<var: 'jumpNotSF' type: #'AbstractInstruction *'>
- 	<var: 'jumpSFZero' type: #'AbstractInstruction *'>
  	jumpNotSF := self genJumpNotSmallFloat: oopReg scratchReg: scratch.
+ 	self genGetSmallFloatValueOf: oopReg scratch: scratch into: dpReg.
+ 	cogit Jump: targetInst.
- 	cogit
- 		MoveR: oopReg R: scratch;
- 		LogicalShiftRightCq: objectMemory numTagBits R: scratch;
- 		CmpCq: 1 R: scratch.
- 	jumpSFZero := cogit JumpAbove: 0.
- 	cogit AddCq: objectMemory smallFloatExponentOffset << (objectMemory smallFloatMantissaBits + 1) R: scratch.
- 	jumpSFZero jmpTarget: (cogit RotateRightCq: 1 R: scratch).
- 	cogit
- 		MoveR: scratch Rd: dpReg;
- 		Jump: targetInst.
  	jumpNotSF jmpTarget: cogit Label.
  	^0!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		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 stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor eip.
  											self writeBackHeadFramePointers];
  		addLine;
  		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: cogit getCStackPointer];
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action:
  			[cogit disassembleCodeAt: (((cogit codeEntryFor: cogit processor pc) isNil
  										  and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  											ifTrue: [instructionPointer]
  											ifFalse: [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]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		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 cog methods with prim...' action: [(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print cog methods with selector...' action:
  			[|s| s := UIManager default request: 'selector'.
  			s notEmpty ifTrue:
  				[s = 'nil' ifTrue: [s := nil].
  				 cogMethodZone methodsDo:
  					[:m|
  					(s ifNil: [m selector = objectMemory nilObject]
  					 ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  							and: [(self str: s
  									n: (m selector + objectMemory baseHeaderSize)
  									cmp: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  		add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  		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', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
- 		add: 'set break pc (', (cogit breakPC isInteger ifTrue: [cogit breakPC hex] ifFalse: [cogit breakPC printString]), ')...-ve to disable' action: [(self promptHex: 'break pc') ifNotNil: [:bpc| cogit breakPC: (bpc >= 0 ifTrue: [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: 'click step' action: [cogit setClickStepBreakBlock];
  		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 block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		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: CogX64Compiler>>hasDoublePrecisionFloatingPointSupport (in category 'testing') -----
  hasDoublePrecisionFloatingPointSupport
+ 	<inline: true>
  	^true!

Item was changed:
  ----- Method: Cogit class>>table:from: (in category 'class initialization') -----
  table: primArray from: specArray 
  	"Fill in the specified entries in the primitive table."
  	specArray do:
+ 		[:spec | 
+ 		 (self shouldIncludeMethodForSelector: spec second) ifTrue:
+ 			[(primArray at: spec first put: CogPrimitiveDescriptor new)
+ 				primitiveGenerator: spec second;
+ 				primNumArgs: (spec at: 3 ifAbsent: -1);
+ 				enabled: (spec at: 4 ifAbsent: nil)]].
- 		[:spec | | descriptor |
- 		(primArray at: spec first put: CogPrimitiveDescriptor new)
- 			primitiveGenerator: spec second;
- 			primNumArgs: (spec at: 3 ifAbsent: -1);
- 			enabled: (spec at: 4 ifAbsent: nil)].
  	primArray object withIndexDo:
  		[:generator :i|
  		generator ifNil:
  			[(primArray object at: i put: CogPrimitiveDescriptor new)
  				primNumArgs: -1]]!

Item was added:
+ ----- Method: Cogit>>breakAt: (in category 'simulation only') -----
+ breakAt: address
+ 	((breakPC isBreakpointFor: address)
+ 	 and: [breakBlock shouldStopIfAtPC: address]) ifTrue:
+ 		[coInterpreter changed: #byteCountText.
+ 		 self halt: 'machine code breakpoint at ', address]!

Item was changed:
  ----- Method: Cogit>>breakBlock: (in category 'simulation only') -----
  breakBlock: aBlock
  	<doNotGenerate>
+ 	breakBlock := aBlock.
+ 	singleStep := singleStep or: [breakPC singleStepRequiredToTriggerIn: self]!
- 	breakBlock := aBlock!

Item was changed:
  ----- Method: Cogit>>breakPC: (in category 'simulation only') -----
+ breakPC: anAddressArrayOrNil
- breakPC: anAddress
  	<doNotGenerate>
+ 	breakPC := anAddressArrayOrNil.
+ 	singleStep := singleStep or: [anAddressArrayOrNil singleStepRequiredToTriggerIn: self]!
- 	breakPC := anAddress.
- 	(breakPC isInteger
- 	 and: [anAddress between: codeBase and: coInterpreter heapBase]) ifTrue:
- 		[singleStep := true].
- 	"If there's a breakPC then it is anded with breakBlock's result, so the breakBlock must default to true.
- 	 If there's no breakPC the break block is used on its own and so must befault to false."
- 	(breakBlock isNil
- 	 or: [breakBlock method = thisContext method]) ifTrue:
- 		[breakBlock := breakPC isInteger
- 						ifTrue: [[:cogit| processor pc = breakPC]]
- 						ifFalse: [[:cogit| false]]]!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: closedPICSize.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
  	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
+ 	self maybeEnableSingleStep.
  	^pic!

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

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
  	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + openPICSize.
+ 	self maybeEnableSingleStep.
  	^pic!

Item was changed:
  ----- Method: Cogit>>generateInstructionsAt: (in category 'generate machine code') -----
  generateInstructionsAt: eventualAbsoluteAddress
  	"Size pc-dependent instructions and assign eventual addresses to all instructions.
  	 Answer the size of the code.
  	 Compute forward branches based on virtual address (abstract code starts at 0),
  	 assuming that any branches branched over are long.
  	 Compute backward branches based on actual address.
  	 Reuse the fixups array to record the pc-dependent instructions that need to have
  	 their code generation postponed until after the others."
  	| absoluteAddress pcDependentIndex abstractInstruction fixup |
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	<var: #fixup type: #'BytecodeFixup *'>
  	absoluteAddress := eventualAbsoluteAddress.
  	pcDependentIndex := 0.
  	0 to: opcodeIndex - 1 do:
  		[:i|
+ 		self maybeBreakAt: absoluteAddress.
- 		breakPC = absoluteAddress ifTrue:
- 			[self halt: 'breakPC reached in generateInstructionsAt:'].
  		abstractInstruction := self abstractInstructionAt: i.
  		abstractInstruction isPCDependent
  			ifTrue:
  				[abstractInstruction sizePCDependentInstructionAt: absoluteAddress.
  				 fixup := self fixupAt: pcDependentIndex.
  				 pcDependentIndex := pcDependentIndex + 1.
  				 fixup instructionIndex: i.
  				 absoluteAddress := absoluteAddress + abstractInstruction machineCodeSize]
  			ifFalse:
  				[absoluteAddress := abstractInstruction concretizeAt: absoluteAddress]].
  	0 to: pcDependentIndex - 1 do:
  		[:j|
  		fixup := self fixupAt: j.
  		abstractInstruction := self abstractInstructionAt: fixup instructionIndex.
+ 		self maybeBreakAt: abstractInstruction address.
- 		breakPC = absoluteAddress ifTrue:
- 			[self halt: 'breakPC reached in generateInstructionsAt:'].
  		abstractInstruction concretizeAt: abstractInstruction address].
- 	self cCode: ''
- 		inSmalltalk:
- 			[breakPC ifNotNil:
- 				[breakPC <= absoluteAddress ifTrue:
- 					[self singleStep: true]]].
  	^absoluteAddress - eventualAbsoluteAddress!

Item was added:
+ ----- Method: Cogit>>maybeBreakAt: (in category 'simulation only') -----
+ maybeBreakAt: address
+ 	((breakPC isBreakpointFor: address)
+ 	 and: [breakBlock shouldStopIfAtPC: address]) ifTrue:
+ 		[coInterpreter changed: #byteCountText.
+ 		 self halt: 'machine code breakpoint at ', address hex, ' in ', thisContext sender selector]!

Item was added:
+ ----- Method: Cogit>>maybeEnableSingleStep (in category 'simulation only') -----
+ maybeEnableSingleStep
+ 	<inline: true>
+ 	self cCode: '' inSmalltalk:
+ 		[singleStep ifFalse: [singleStep := breakPC singleStepRequiredToTriggerIn: self]]!

Item was added:
+ ----- Method: Cogit>>promptForBreakPC (in category 'simulation only') -----
+ promptForBreakPC
+ 	<doNotGenerate>
+ 	| s first pc |
+ 	s := UIManager default request: 'Break pc (hex)'.
+ 	s := s withBlanksTrimmed.
+ 	s isEmpty ifTrue: [^self].
+ 	('+-' includes: s first) ifTrue: [first := s first. s := s allButFirst].
+ 	(s isEmpty and: [first = $-]) ifTrue:
+ 		[^self breakPC: nil].
+ 	pc := (s includes: $r)
+ 			ifTrue:
+ 				[Number readFrom: s readStream]
+ 			ifFalse:
+ 				[(#('0x' '-0x') detect: [:prefix| s beginsWith: prefix] ifNone: []) ifNotNil:
+ 					[:prefix|
+ 					s := s allButFirst: prefix size.
+ 					prefix first = $- ifTrue: [s := '-', s]].
+ 				Integer readFrom: s readStream base: 16].
+ 	first = $+ ifTrue:
+ 		[^self breakPC: (breakPC addBreakpoint: pc)].
+ 	first = $- ifTrue:
+ 		[^self breakPC: (breakPC removeBreakpoint: pc)].
+ 	self breakPC: pc!

Item was changed:
  ----- Method: Cogit>>setClickStepBreakBlock (in category 'simulation only') -----
  setClickStepBreakBlock
  	"Set the break block to present a confirmer, breaking if true, and restoring the previous break block.
  	 If an open debugger on the receiver can be found, proceed it."
  	<doNotGenerate>
+ 	| previousBreakBlock previousBreakPC previousSingleStep |
+ 	(breakBlock isNil or: [breakBlock method ~~ thisContext method]) ifTrue:
+ 		[previousBreakBlock := breakBlock.
+ 		 previousBreakPC := breakPC.
+ 		 previousSingleStep := singleStep.
+ 		 breakBlock := [:ign|
+ 						(processor pc ~= previousBreakPC
+ 						 and: [UIManager confirm: 'step?'])
+ 							ifTrue: [false]
+ 							ifFalse: [breakBlock := previousBreakBlock.
+ 									breakPC := previousBreakPC.
+ 									singleStep := previousSingleStep.
+ 									true]].
+ 		 singleStep := breakPC := true].
- 	| previousBreakBlock previousBreakPC |
- 	previousBreakBlock := breakBlock.
- 	previousBreakPC := breakPC.
- 	breakBlock := [:ign|
- 					(processor pc ~= previousBreakPC
- 					 and: [UIManager confirm: 'step?'])
- 						ifTrue: [false]
- 						ifFalse: [breakBlock := previousBreakBlock.
- 								breakPC := previousBreakPC.
- 								true]].
- 	singleStep := true.
- 	breakPC := nil.
  	(World submorphs
  		detect:
  			[:m|
  			 m model class == Debugger
  			 and: [(m model interruptedProcess suspendedContext findContextSuchThat:
  					[:ctxt|
  					ctxt receiver == self
  					and: [ctxt selector == #simulateCogCodeAt:]]) notNil]]
  		ifNone: []) ifNotNil:
  			[:debuggerWindow|
  			 WorldState addDeferredUIMessage:
  				[debuggerWindow model proceed]]!

Item was changed:
  ----- Method: Cogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	coInterpreter := aCoInterpreter.
  	objectMemory := aCoInterpreter objectMemory.
  	threadManager := aCoInterpreter threadManager. "N.B. may be nil"
  	methodZone := CogMethodZone new.
  	objectRepresentation := objectMemory objectRepresentationClass
  								forCogit: self methodZone: methodZone.
  	methodZone setInterpreter: aCoInterpreter
  				objectRepresentation: objectRepresentation
  				cogit: self.
  	generatorTable := self class generatorTable.
  	primitiveGeneratorTable := self class primitiveTable.
  	processor := ProcessorClass new.
  	simulatedAddresses := Dictionary new.
  	simulatedTrampolines := Dictionary new.
  	simulatedVariableGetters := Dictionary new.
  	simulatedVariableSetters := Dictionary new.
  	traceStores := 0.
  	traceFlags := (self class initializationOptions at: #recordPrimTrace ifAbsent: [true])
  					ifTrue: [8] "record prim trace on by default (see Cogit class>>decareCVarsIn:)"
  					ifFalse: [0].
  	debugPrimCallStackOffset := 0.
  	singleStep := printRegisters := printInstructions := clickConfirm := false.
- 	breakBlock ifNil: [self breakPC: breakPC].
  	backEnd := CogCompilerClass for: self.
  	methodLabel := CogCompilerClass for: self.
  	(literalsManager := backEnd class literalsManagerClass new) cogit: self.
  	ordinarySendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	superSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[directedSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	NewspeakVM ifTrue:
  		[selfSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		dynamicSuperSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		implicitReceiverSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines).
  		outerSendTrampolines := CArrayAccessor on: (Array new: NumSendTrampolines)].
  	"debug metadata"
  	objectReferencesInRuntime := CArrayAccessor on: (Array new: NumObjRefsInRuntime).
  	runtimeObjectRefIndex := 0.
  	"debug metadata"
  	trampolineAddresses := CArrayAccessor on: (Array new: NumTrampolines * 2).
  	trampolineTableIndex := 0.
  
  	extA := extB := 0.
  
  	compilationTrace ifNil: [compilationTrace := self class initializationOptions at: #compilationTrace ifAbsent: [0]].
  	debugOpcodeIndices := self class initializationOptions at: #debugOpcodeIndices ifAbsent: [Set new].!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
+ 	[[[singleStep
+ 		ifTrue:
+ 			[[processor sp < stackZoneBase ifTrue: [self halt].
+ 			  self recordProcessing.
+ 			  self maybeBreakAt: processor pc] value. "So that the Debugger's Over steps over all this"
+ 			  processor
- 	[[[singleStep ifTrue:
- 		[[processor sp < stackZoneBase ifTrue: [self halt].
- 		  self recordProcessing.
- 		  (breakPC isInteger
- 			ifTrue:
- 				[processor pc = breakPC
- 				 and: [breakBlock value: self]]
- 			ifFalse:
- 				[breakBlock value: self]) ifTrue:
- 			["printRegisters := printInstructions := true"
- 			 "self reportLastNInstructions"
- 			 "coInterpreter printExternalHeadFrame"
- 			 "coInterpreter printFrameAndCallers: coInterpreter framePointer SP: coInterpreter stackPointer"
- 			 "coInterpreter shortPrintFrameAndCallers: coInterpreter framePointer"
- 			 "coInterpreter printFrame: processor fp WithSP: processor sp"
- 			 "coInterpreter printFrameAndCallers: processor fp SP: processor sp"
- 			 "coInterpreter shortPrintFrameAndCallers: processor fp"
- 			"self disassembleMethodFor: processor pc"
- 			 coInterpreter changed: #byteCountText.
- 			 self halt: 'machine code breakpoint at ', processor pc hex]] value]. "So that the Debugger's Over steps over all this"
- 	   singleStep
- 		ifTrue: [processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd]
+ 		ifFalse:
+ 			[processor
- 		ifFalse: [processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd].
  	   ((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
  			[self halt]].
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
  		do: [:ex| self handleSimulationTrap: ex].
  	 true] whileTrue!

Item was added:
+ ----- Method: Integer>>addBreakpoint: (in category '*VMMaker-interpreter simulator') -----
+ addBreakpoint: address
+ 	^{self. address}!

Item was added:
+ ----- Method: Integer>>isActiveBreakpoint (in category '*VMMaker-interpreter simulator') -----
+ isActiveBreakpoint
+ 	^true!

Item was added:
+ ----- Method: Integer>>isBreakpointFor: (in category '*VMMaker-interpreter simulator') -----
+ isBreakpointFor: address
+ 	^self = address!

Item was added:
+ ----- Method: Integer>>menuPrompt (in category '*VMMaker-interpreter simulator') -----
+ menuPrompt
+ 	^' (', self hex, ')'!

Item was added:
+ ----- Method: Integer>>removeBreakpoint: (in category '*VMMaker-interpreter simulator') -----
+ removeBreakpoint: address
+ 	^nil!

Item was added:
+ ----- Method: Integer>>singleStepRequiredToTriggerIn: (in category '*VMMaker-interpreter simulator') -----
+ singleStepRequiredToTriggerIn: aCogit
+ 	^self between: aCogit cogCodeBase and: aCogit methodZone limitZony!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForNewsqueak (in category 'class initialization') -----
  initializePrimitiveTableForNewsqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueakV3"
+ 	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
+ 										ifTrue: [555]
+ 										ifFalse: [222].
- 	MaxCompiledPrimitiveIndex := 222.
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1	mclassIsSmallInteger:)
  		(2 genPrimitiveSubtract			1	mclassIsSmallInteger:)
  		(3 genPrimitiveLessThan		1	mclassIsSmallInteger:)
  		(4 genPrimitiveGreaterThan		1	mclassIsSmallInteger:)
  		(5 genPrimitiveLessOrEqual		1	mclassIsSmallInteger:)
  		(6 genPrimitiveGreaterOrEqual	1	mclassIsSmallInteger:)
  		(7 genPrimitiveEqual			1	mclassIsSmallInteger:)
  		(8 genPrimitiveNotEqual		1	mclassIsSmallInteger:)
  		(9 genPrimitiveMultiply			1	processorHasMultiplyAndMClassIsSmallInteger:)
  		(10 genPrimitiveDivide			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(11 genPrimitiveMod			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(12 genPrimitiveDiv				1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(13 genPrimitiveQuo			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(14 genPrimitiveBitAnd			1	mclassIsSmallInteger:)
  		(15 genPrimitiveBitOr			1	mclassIsSmallInteger:)
  		(16 genPrimitiveBitXor			1	mclassIsSmallInteger:)
  		(17 genPrimitiveBitShift			1	mclassIsSmallInteger:)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
  		"(38 primitiveFloatAt)"
  		"(39 primitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
  		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
  		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
  		"(51 primitiveTruncated)"
  		"(52 primitiveFractionalPart)"
  		"(53 primitiveExponent)"
  		"(54 primitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
  		"(56 primitiveSine)"
  		"(57 primitiveArctan)"
  		"(58 primitiveLogN)"
  		"(59 primitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew)				"For VMMirror support 1 argument instantiateFixedClass: as well as baiscNew"
  		(71 genPrimitiveNewWithArg)		"For VMMirror support 2 argument instantiateVariableClass:withSize: as well as baiscNew:"
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)			"For objectClass: and VMMirror support 1 argument classOf: as well as class"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)			"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveCharacterValue 0)	"Character>>value"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
+ 		"SmallFloat primitives (540-559)"
+ 		(541 genPrimitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(542 genPrimitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(543 genPrimitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(544 genPrimitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(545 genPrimitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(546 genPrimitiveSmallFloatGreaterOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(547 genPrimitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(548 genPrimitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(549 genPrimitiveSmallFloatMultiply				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(550 genPrimitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(551 genPrimitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(552 genPrimitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(553 genPrimitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(554 genPrimitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		(555 genPrimitiveSmallFloatSquareRoot			0	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(556 genPrimitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(557 genPrimitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(558 genPrimitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(559 genPrimitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(541 primitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(542 primitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(543 primitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(544 primitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(545 primitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(546 primitiveSmallFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(547 primitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(548 primitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(549 primitiveSmallFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(550 primitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(551 primitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(552 primitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(553 primitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(554 primitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(555 primitiveSmallFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(556 primitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(557 primitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(558 primitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(559 primitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
  	)!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak (in category 'class initialization') -----
  initializePrimitiveTableForSqueak
  	"Initialize the table of primitive generators.  This does not include normal primitives implemented in the coInterpreter.
  	 N.B. primitives that don't have an explicit arg count (the integer following the generator) may be variadic."
  	"SimpleStackBasedCogit initializePrimitiveTableForSqueak"
+ 	MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8
+ 										ifTrue: [555]
+ 										ifFalse: [222].
- 	MaxCompiledPrimitiveIndex := 222.
  	primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + 1).
  	self table: primitiveTable from: 
  	#(	"Integer Primitives (0-19)"
  		(1 genPrimitiveAdd				1	mclassIsSmallInteger:)
  		(2 genPrimitiveSubtract			1	mclassIsSmallInteger:)
  		(3 genPrimitiveLessThan		1	mclassIsSmallInteger:)
  		(4 genPrimitiveGreaterThan		1	mclassIsSmallInteger:)
  		(5 genPrimitiveLessOrEqual		1	mclassIsSmallInteger:)
  		(6 genPrimitiveGreaterOrEqual	1	mclassIsSmallInteger:)
  		(7 genPrimitiveEqual			1	mclassIsSmallInteger:)
  		(8 genPrimitiveNotEqual		1	mclassIsSmallInteger:)
  		(9 genPrimitiveMultiply			1	processorHasMultiplyAndMClassIsSmallInteger:)
  		(10 genPrimitiveDivide			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(11 genPrimitiveMod			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(12 genPrimitiveDiv				1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(13 genPrimitiveQuo			1	processorHasDivQuoRemAndMClassIsSmallInteger:)
  		(14 genPrimitiveBitAnd			1	mclassIsSmallInteger:)
  		(15 genPrimitiveBitOr			1	mclassIsSmallInteger:)
  		(16 genPrimitiveBitXor			1	mclassIsSmallInteger:)
  		(17 genPrimitiveBitShift			1	mclassIsSmallInteger:)
  		"(18 primitiveMakePoint)"
  		"(19 primitiveFail)"					"Guard primitive for simulation -- *must* fail"
  
  		"LargeInteger Primitives (20-39)"
  		"(20 primitiveFail)"
  		"(21 primitiveAddLargeIntegers)"
  		"(22 primitiveSubtractLargeIntegers)"
  		"(23 primitiveLessThanLargeIntegers)"
  		"(24 primitiveGreaterThanLargeIntegers)"
  		"(25 primitiveLessOrEqualLargeIntegers)"
  		"(26 primitiveGreaterOrEqualLargeIntegers)"
  		"(27 primitiveEqualLargeIntegers)"
  		"(28 primitiveNotEqualLargeIntegers)"
  		"(29 primitiveMultiplyLargeIntegers)"
  		"(30 primitiveDivideLargeIntegers)"
  		"(31 primitiveModLargeIntegers)"
  		"(32 primitiveDivLargeIntegers)"
  		"(33 primitiveQuoLargeIntegers)"
  		"(34 primitiveBitAndLargeIntegers)"
  		"(35 primitiveBitOrLargeIntegers)"
  		"(36 primitiveBitXorLargeIntegers)"
  		"(37 primitiveBitShiftLargeIntegers)"
  
  		"Float Primitives (38-59)"
+ 		"(38 genPrimitiveFloatAt)"
+ 		"(39 genPrimitiveFloatAtPut)"
- 		"(38 primitiveFloatAt)"
- 		"(39 primitiveFloatAtPut)"
  		(40 genPrimitiveAsFloat					0	processorHasDoublePrecisionFloatingPointSupport:)
  		(41 genPrimitiveFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(42 genPrimitiveFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(43 genPrimitiveFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(44 genPrimitiveFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(45 genPrimitiveFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
  		(46 genPrimitiveFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)
  		(47 genPrimitiveFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
  		(48 genPrimitiveFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(49 genPrimitiveFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)
  		(50 genPrimitiveFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(51 genPrimitiveTruncated)"
+ 		"(52 genPrimitiveFractionalPart)"
+ 		"(53 genPrimitiveExponent)"
+ 		"(54 genPrimitiveTimesTwoPower)"
- 		"(51 primitiveTruncated)"
- 		"(52 primitiveFractionalPart)"
- 		"(53 primitiveExponent)"
- 		"(54 primitiveTimesTwoPower)"
  		(55 genPrimitiveFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(56 genPrimitiveSine)"
+ 		"(57 genPrimitiveArctan)"
+ 		"(58 genPrimitiveLogN)"
+ 		"(59 genPrimitiveExp)"
- 		"(56 primitiveSine)"
- 		"(57 primitiveArctan)"
- 		"(58 primitiveLogN)"
- 		"(59 primitiveExp)"
  
  		"Subscript and Stream Primitives (60-67)"
  		(60 genPrimitiveAt				1)
  		(61 genPrimitiveAtPut			2)
  		(62 genPrimitiveSize			0)
  		(63 genPrimitiveStringAt		1)
  		(64 genPrimitiveStringAtPut		2)
  		"The stream primitives no longer pay their way; normal Smalltalk code is faster."
  		(65 genFastPrimFail)"was primitiveNext"
  		(66 genFastPrimFail) "was primitiveNextPut"
  		(67 genFastPrimFail) "was primitiveAtEnd"
  
  		"StorageManagement Primitives (68-79)"
  		(68 genPrimitiveObjectAt			1)	"Good for debugger/InstructionStream performance"
  		"(69 primitiveObjectAtPut)"
  		(70 genPrimitiveNew			0)
  		(71 genPrimitiveNewWithArg	1)
  		"(72 primitiveArrayBecomeOneWay)"		"Blue Book: primitiveBecome"
  		"(73 primitiveInstVarAt)"
  		"(74 primitiveInstVarAtPut)"
  		(75 genPrimitiveIdentityHash	0)
  		"(76 primitiveStoreStackp)"					"Blue Book: primitiveAsObject"
  		"(77 primitiveSomeInstance)"
  		"(78 primitiveNextInstance)"
  		(79 genPrimitiveNewMethod	2)
  
  		"Control Primitives (80-89)"
  		"(80 primitiveFail)"							"Blue Book: primitiveBlockCopy"
  		"(81 primitiveFail)"							"Blue Book: primitiveValue"
  		"(82 primitiveFail)"							"Blue Book: primitiveValueWithArgs"
  		(83 genPrimitivePerform)
  		"(84 primitivePerformWithArgs)"
  		"(85 primitiveSignal)"
  		"(86 primitiveWait)"
  		"(87 primitiveResume)"
  		"(88 primitiveSuspend)"
  		"(89 primitiveFlushCache)"
  
  		"System Primitives (110-119)"
  		(110 genPrimitiveIdentical 1)
  		(111 genPrimitiveClass)				"Support both class and Context>>objectClass:"
  		"(112 primitiveBytesLeft)"
  		"(113 primitiveQuit)"
  		"(114 primitiveExitToDebugger)"
  		"(115 primitiveChangeClass)"					"Blue Book: primitiveOopsLeft"
  		"(116 primitiveFlushCacheByMethod)"
  		"(117 primitiveExternalCall)"
  		"(118 primitiveDoPrimitiveWithArgs)"
  		"(119 primitiveFlushCacheSelective)"
  
  		(169 genPrimitiveNotIdentical 1)
  
  		(170 genPrimitiveAsCharacter)			"SmallInteger>>asCharacter, Character class>>value:"
  		(171 genPrimitiveCharacterValue 0)	"Character>>value"
  			
  		"(173 primitiveSlotAt 1)"
  		"(174 primitiveSlotAtPut 2)"
  		(175 genPrimitiveIdentityHash	0)		"Behavior>>identityHash"
  
  		"Old closure primitives"
  		"(186 primitiveFail)" "was primitiveClosureValue"
  		"(187 primitiveFail)" "was primitiveClosureValueWithArgs"
  
  		"Perform method directly"
  		"(188 primitiveExecuteMethodArgsArray)"
  		"(189 primitiveExecuteMethod)"
  
  		"Unwind primitives"
  		"(195 primitiveFindNextUnwindContext)"
  		"(196 primitiveTerminateTo)"
  		"(197 primitiveFindHandlerContext)"
  		(198 genFastPrimFail "primitiveMarkUnwindMethod")
  		(199 genFastPrimFail "primitiveMarkHandlerMethod")
  
  		"new closure primitives"
  		"(200 primitiveClosureCopyWithCopiedValues)"
  		(201 genPrimitiveClosureValue	0) "value"
  		(202 genPrimitiveClosureValue	1) "value:"
  		(203 genPrimitiveClosureValue	2) "value:value:"
  		(204 genPrimitiveClosureValue	3) "value:value:value:"
  		(205 genPrimitiveClosureValue	4) "value:value:value:value:"
  		"(206 genPrimitiveClosureValueWithArgs)" "valueWithArguments:"
  
  		"(210 primitiveContextAt)"
  		"(211 primitiveContextAtPut)"
  		"(212 primitiveContextSize)"
  
  		"(218 primitiveDoNamedPrimitiveWithArgs)"
  		"(219 primitiveFail)"	"reserved for Cog primitives"
  
  		"(220 primitiveFail)"		"reserved for Cog primitives"
  
  		(221 genPrimitiveClosureValue	0) "valueNoContextSwitch"
  		(222 genPrimitiveClosureValue	1) "valueNoContextSwitch:"
  
+ 		"SmallFloat primitives (540-559)"
+ 		(541 genPrimitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(542 genPrimitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(543 genPrimitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(544 genPrimitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(545 genPrimitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(546 genPrimitiveSmallFloatGreaterOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(547 genPrimitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(548 genPrimitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(549 genPrimitiveSmallFloatMultiply				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		(550 genPrimitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(551 genPrimitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(552 genPrimitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(553 genPrimitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(554 genPrimitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		(555 genPrimitiveSmallFloatSquareRoot			0	processorHasDoublePrecisionFloatingPointSupport:)
+ 		"(556 genPrimitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(557 genPrimitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(558 genPrimitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
+ 		"(559 genPrimitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(541 primitiveSmallFloatAdd				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(542 primitiveSmallFloatSubtract			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(543 primitiveSmallFloatLessThan			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(544 primitiveSmallFloatGreaterThan		1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(545 primitiveSmallFloatLessOrEqual		1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(546 primitiveSmallFloatGreaterOrEqual	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(547 primitiveSmallFloatEqual				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(548 primitiveSmallFloatNotEqual			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(549 primitiveSmallFloatMultiply			1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(550 primitiveSmallFloatDivide				1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(551 primitiveSmallFloatTruncated			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(552 primitiveSmallFloatFractionalPart		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(553 primitiveSmallFloatExponent			0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(554 primitiveSmallFloatTimesTwoPower	1	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(555 primitiveSmallFloatSquareRoot		0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(556 primitiveSmallFloatSine				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(557 primitiveSmallFloatArctan				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(558 primitiveSmallFloatLogN				0	processorHasDoublePrecisionFloatingPointSupport:)"
- 		"(559 primitiveSmallFloatExp				0	processorHasDoublePrecisionFloatingPointSupport:)"
  	)!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatAdd (in category 'primitive generators') -----
+ genPrimitiveSmallFloatAdd
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: AddRdRd preOpCheck: nil!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatDivide (in category 'primitive generators') -----
+ genPrimitiveSmallFloatDivide
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: DivRdRd preOpCheck: #genDoubleFailIfZeroArgRcvr:arg:!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPEqual: invert: false!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatGreaterOrEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatGreaterOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: false!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatGreaterThan (in category 'primitive generators') -----
+ genPrimitiveSmallFloatGreaterThan
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreater: invert: false!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatLessOrEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatLessOrEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreaterOrEqual: invert: true!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatLessThan (in category 'primitive generators') -----
+ genPrimitiveSmallFloatLessThan
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPGreater: invert: true!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatMultiply (in category 'primitive generators') -----
+ genPrimitiveSmallFloatMultiply
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: MulRdRd preOpCheck: nil!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatNotEqual (in category 'primitive generators') -----
+ genPrimitiveSmallFloatNotEqual
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatComparison: #JumpFPNotEqual: invert: false!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
+ genPrimitiveSmallFloatSquareRoot
+ 	<option: #Spur64BitMemoryManager>
+ 	"Stack looks like
+ 		receiver (also in ResultReceiverReg)
+ 		return address"
+ 	| jumpFailAlloc |
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg into: DPFPReg0.
+ 	self SqrtRd: DPFPReg0.
+ 	jumpFailAlloc := objectRepresentation
+ 					genAllocFloatValue: DPFPReg0
+ 					into: SendNumArgsReg
+ 					scratchReg: ClassReg
+ 					scratchReg: TempReg.
+ 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	self RetN: (self primRetNOffsetFor: 0).
+ 	jumpFailAlloc jmpTarget: self Label.
+ 	^self compileFallbackToInterpreterPrimitive: 0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPrimitiveSmallFloatSubtract (in category 'primitive generators') -----
+ genPrimitiveSmallFloatSubtract
+ 	<option: #Spur64BitMemoryManager>
+ 	^self genSmallFloatArithmetic: SubRdRd preOpCheck: nil!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genSmallFloatArithmetic:preOpCheck: (in category 'primitive generators') -----
+ genSmallFloatArithmetic: 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 |
+ 	<var: #jumpFailClass type: #'AbstractInstruction *'>
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
+ 	<var: #doOp type: #'AbstractInstruction *'>
+ 	<var: #fail type: #'AbstractInstruction *'>
+ 	self genLoadArgAtDepth: 0 into: ClassReg.
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
+ 	objectRepresentation genCmpClassFloatCompactIndexR: 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 RetN: (self primRetNOffsetFor: 1).
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
+ 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	self ConvertR: ClassReg Rd: DPFPReg1.
+ 	self Jump: doOp.
+ 	jumpFailAlloc jmpTarget: self Label.
+ 	self compileFallbackToInterpreterPrimitive: 0.
+ 	fail := self Label.
+ 	jumpFailClass jmpTarget: fail.
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck jmpTarget: fail].
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: fail].
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
+ genSmallFloatComparison: 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 *'>
+ 	<var: #jumpCond type: #'AbstractInstruction *'>
+ 	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 
+ 	self genLoadArgAtDepth: 0 into: ClassReg.
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	jumpImmediate := objectRepresentation genJumpImmediate: ClassReg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: ClassReg into: SendNumArgsReg.
+ 	objectRepresentation genCmpClassFloatCompactIndexR: 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 genMoveFalseR: ReceiverResultReg.
+ 	self RetN: (self primRetNOffsetFor: 1).
+ 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
+ 	self RetN: (self primRetNOffsetFor: 1).
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation maybeGenConvertIfSmallFloatIn: ClassReg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: ClassReg scratchReg: TempReg].
+ 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	self ConvertR: ClassReg Rd: DPFPReg1.
+ 	self Jump: compare.
+ 	jumpFail jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
+ 	^0!

Item was added:
+ ----- Method: SmallInteger>>isBreakpointFor: (in category '*VMMaker-interpreter simulator') -----
+ isBreakpointFor: address
+ 	<primitive: 7>
+ 	^self = address!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>smallFloatExponentBits (in category 'interpreter access') -----
+ smallFloatExponentBits
+ 	"SmallFloat64's have the same mantissa as IEEE single-precision floating point"
+ 	<api>
+ 	<cmacro>
+ 	^8!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>smallFloatMantissaBits (in category 'interpreter access') -----
  smallFloatMantissaBits
+ 	"SmallFloat64's have the same mantissa as IEEE double-precision floating point"
- 	"SmallFLoat64's have the same mantissa as IEEE double-precision floating point"
  	<api>
  	<cmacro>
  	^52!

Item was changed:
  ----- Method: StackInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: StackInterpreter class>>table:from: (in category 'initialization') -----
  table: anArray from: specArray 
  	"SpecArray is an array of one of (index selector) or (index1 
  	 index2 selector) or (index nil) or (index1 index2 nil).  If selector
  	 then the entry is the selector, but if nil the entry is the index."
  	| contiguous |
  	contiguous := 0.
  	specArray do:
  		[:spec | 
  		(spec at: 1) = contiguous ifFalse:
  			[self error: 'Non-contiguous table entry'].
  		spec size = 2
  			ifTrue:
  				[anArray
  					at: (spec at: 1) + 1
  					put: ((spec at: 2) ifNil: [spec at: 1] ifNotNil: [:sym| sym]).
  				 contiguous := contiguous + 1]
  			ifFalse:
  				[(spec at: 1) to: (spec at: 2) do:
  					[:i | anArray at: i + 1 put: ((spec at: 3) ifNil: [i] ifNotNil: [:sym| sym])].
  				 contiguous := contiguous + ((spec at: 2) - (spec at: 1)) + 1]].
  	anArray doWithIndex:
  		[:entry :index|
  		entry isSymbol ifTrue:
+ 			[(self shouldIncludeMethodForSelector: entry) ifFalse:
+ 				[anArray at: index put: 0]]]!
- 			[(self whichClassIncludesSelector: entry) ifNotNil:
- 				[:c| | m |
- 				m := c >> entry.
- 				(m pragmaAt: #option:) ifNotNil:
- 					[:pragma|
- 					(initializationOptions at: (pragma arguments first) ifAbsent: [true]) ifFalse:
- 						[anArray at: index put: 0]]]]]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimitiveSmallFloatSquareRoot (in category 'primitive generators') -----
+ genPrimitiveSmallFloatSquareRoot
+ 	<option: #Spur64BitMemoryManager>
+ 	| jumpFailAlloc |
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg into: DPFPReg0.
+ 	self SqrtRd: DPFPReg0.
+ 	jumpFailAlloc := objectRepresentation
+ 						genAllocFloatValue: DPFPReg0
+ 						into: SendNumArgsReg
+ 						scratchReg: ClassReg
+ 						scratchReg: TempReg.
+ 	self MoveR: SendNumArgsReg R: ReceiverResultReg.
+ 	self RetN: 0.
+ 	jumpFailAlloc jmpTarget: self Label.
+ 	^self compileFallbackToInterpreterPrimitive: 0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genSmallFloatArithmetic:preOpCheck: (in category 'primitive generators') -----
+ genSmallFloatArithmetic: arithmeticOperator preOpCheck: preOpCheckOrNil
+ 	"Receiver and arg in registers.
+ 	 Stack looks like
+ 		return address"
+ 	<var: #preOpCheckOrNil declareC: 'AbstractInstruction *(*preOpCheckOrNil)(int rcvrReg, int argReg)'>
+ 	| jumpFailClass jumpFailClass2 jumpFailAlloc jumpFailCheck jumpImmediate jumpNonInt doOp |
+ 	<var: #jumpFailClass type: #'AbstractInstruction *'>
+ 	<var: #jumpFailClass2 type: #'AbstractInstruction *'>
+ 	<var: #jumpFailAlloc type: #'AbstractInstruction *'>
+ 	<var: #jumpImmediate type: #'AbstractInstruction *'>
+ 	<var: #jumpNonInt type: #'AbstractInstruction *'>
+ 	<var: #jumpFailCheck type: #'AbstractInstruction *'>
+ 	<var: #doOp type: #'AbstractInstruction *'>
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	self MoveR: Arg0Reg R: ClassReg.
+ 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	objectRepresentation genCmpClassFloatCompactIndexR: 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.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: doOp.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
+ 	objectRepresentation genConvertSmallIntegerToIntegerInReg: ClassReg.
+ 	self ConvertR: ClassReg Rd: DPFPReg1.
+ 	self Jump: doOp.
+ 	"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.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFailClass getJmpTarget].
+ 	preOpCheckOrNil ifNotNil:
+ 		[jumpFailCheck jmpTarget: jumpFailClass getJmpTarget].
+ 	backEnd genPushRegisterArgsForNumArgs: methodOrBlockNumArgs scratchReg: SendNumArgsReg.
+ 	jumpFailClass2 := self Jump: 0.
+ 	jumpFailAlloc jmpTarget: self Label.
+ 	self compileFallbackToInterpreterPrimitive: 0.
+ 	jumpFailClass2 jmpTarget: self Label.
+ 	^0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genSmallFloatComparison:invert: (in category 'primitive generators') -----
+ genSmallFloatComparison: 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 *'>
+ 	<var: #jumpCond type: #'AbstractInstruction *'>
+ 	<var: #compare type: #'AbstractInstruction *'>
+ 	<var: #jumpFail type: #'AbstractInstruction *'>
+ 	objectRepresentation genGetSmallFloatValueOf: ReceiverResultReg scratch: SendNumArgsReg into: DPFPReg0.
+ 	jumpImmediate := objectRepresentation genJumpImmediate: Arg0Reg.
+ 	objectRepresentation genGetCompactClassIndexNonImmOf: Arg0Reg into: SendNumArgsReg.
+ 	objectRepresentation genCmpClassFloatCompactIndexR: 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 genMoveFalseR: ReceiverResultReg.
+ 	self RetN: 0.
+ 	jumpCond jmpTarget: (self genMoveTrueR: ReceiverResultReg).
+ 	self RetN: 0.
+ 	jumpImmediate jmpTarget: self Label.
+ 	objectRepresentation maybeGenConvertIfSmallFloatIn: Arg0Reg scratchReg: TempReg into: DPFPReg1 andJumpTo: compare.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg].
+ 	objectRepresentation genConvertSmallIntegerToIntegerInReg: Arg0Reg.
+ 	self ConvertR: Arg0Reg Rd: DPFPReg1.
+ 	self Jump: compare.
+ 	jumpFail jmpTarget: self Label.
+ 	objectRepresentation smallIntegerIsOnlyImmediateType ifFalse:
+ 		[jumpNonInt jmpTarget: jumpFail getJmpTarget].
+ 	^0!

Item was added:
+ ----- Method: UndefinedObject>>addBreakpoint: (in category '*VMMaker-interpreter simulator') -----
+ addBreakpoint: address
+ 	^address!

Item was added:
+ ----- Method: UndefinedObject>>isActiveBreakpoint (in category '*VMMaker-interpreter simulator') -----
+ isActiveBreakpoint
+ 	^false!

Item was added:
+ ----- Method: UndefinedObject>>isBreakpointFor: (in category '*VMMaker-interpreter simulator') -----
+ isBreakpointFor: address
+ 	^false!

Item was added:
+ ----- Method: UndefinedObject>>menuPrompt (in category '*VMMaker-interpreter simulator') -----
+ menuPrompt
+ 	^''!

Item was added:
+ ----- Method: UndefinedObject>>shouldStopIfAtPC: (in category '*VMMaker-interpreter simulator') -----
+ shouldStopIfAtPC: address
+ 	^true!

Item was added:
+ ----- Method: UndefinedObject>>singleStepRequiredToTriggerIn: (in category '*VMMaker-interpreter simulator') -----
+ singleStepRequiredToTriggerIn: aCogit
+ 	^false!

Item was added:
+ ----- Method: VMClass class>>shouldIncludeMethodForSelector: (in category 'translation') -----
+ shouldIncludeMethodForSelector: selector
+ 	"Answer whether a primitive method shoud be translated.  Emit a warning to the transcript if the method doesn't exist."
+ 	^(self whichClassIncludesSelector: selector)
+ 		ifNotNil:
+ 			[:c|
+ 			 (c >> selector pragmaAt: #option:)
+ 				ifNotNil:
+ 					[:pragma|
+ 					 initializationOptions at: (pragma arguments first) ifAbsent: [true]]
+ 				ifNil: [true]]
+ 		ifNil:
+ 			[Transcript nextPutAll: 'Cannot find implementation of '; nextPutAll: selector; nextPutAll: ' in hierarchy of '; print: self; cr; flush.
+ 			 false]!



More information about the Vm-dev mailing list