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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 5 19:39:35 UTC 2015


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

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

Name: VMMaker.oscog-eem.1553
Author: eem
Time: 5 December 2015, 11:37:56.127 am
UUID: 85428a3c-bbe7-43dd-876e-625f56beda91
Ancestors: VMMaker.oscog-eem.1552

Cogit: Implement overflow checking for primitive div that works in 32- and 64-bits.

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

Item was added:
+ ----- Method: CogObjectRepresentation>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
+ genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
+ 	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump."
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationFor32BitSpur>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
+ genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
+ 	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
+ 	 c.f. Spur32BitMemoryManager>>isIntegerValue:"
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		MoveR: aRegister R: scratchReg;
+ 		ArithmeticShiftRightCq: 1 R: scratchReg;
+ 		XorR: aRegister R: scratchReg;
+ 		JumpLess: 0!

Item was added:
+ ----- Method: CogObjectRepresentationFor64BitSpur>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
+ genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
+ 	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
+ 	 c.f. Spur64BitMemoryManager>>isIntegerValue:"
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		MoveR: aRegister R: scratchReg;
+ 		ArithmeticShiftRightCq: 64 - self numTagBits R: scratchReg;
+ 		AddCq: 1 R: scratchReg;
+ 		AndCq: 1 << (self numTagBits + 1) - 1 R: scratchReg; "sign and top numTags bits must be the same"
+ 		CmpCq: 1 R: scratchReg;
+ 		JumpGreaterOrEqual: 0!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>genJumpIsSmallIntegerValue:scratch: (in category 'compile abstract instructions') -----
+ genJumpIsSmallIntegerValue: aRegister scratch: scratchReg
+ 	"Generate a test for aRegister containing an integer value in the SmallInteger range, and a jump if so, answering the jump.
+ 	 c.f. ObjectMemory>>isIntegerValue:"
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit
+ 		MoveR: aRegister R: scratchReg;
+ 		ArithmeticShiftRightCq: 1 R: scratchReg;
+ 		XorR: aRegister R: scratchReg;
+ 		JumpLess: 0!

Item was changed:
  ----- Method: CogVMSimulator>>dispatchOn:in: (in category 'interpreter shell') -----
  dispatchOn: anInteger in: selectorArray
  	"Simulate a case statement via selector table lookup.
  	The given integer must be between 0 and selectorArray size-1, inclusive.
  	For speed, no range test is done, since it is done by the at: operation.
  	Note that, unlike many other arrays used in the Interpreter, this method expect NO CArrayAccessor wrapping - it would duplicate the +1. Maybe this would be better updated to make it all uniform"
+ 	cogit breakPC ifNil:
+ 		[cogit breakBlock ifNotNil:
+ 			[:bb| (bb value: cogit) ifTrue: [self halt: 'breakpoint reached']]].
- 	cogit breakBlock ifNotNil:
- 		[:bb| (bb value: cogit) ifTrue: [self halt: 'breakpoint reached']].
  	self perform: (selectorArray at: (anInteger + 1)).!

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 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: 'set break pc (', (cogit breakPC isInteger ifTrue: [cogit breakPC hex] ifFalse: [cogit breakPC printString]), ')...' 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: '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: SimpleStackBasedCogit>>genPrimitiveDiv (in category 'primitive generators') -----
  genPrimitiveDiv
+ 	| jumpNotSI jumpIsSI jumpZero jumpExact jumpSameSign convert |
- 	| jumpNotSI jumpZero jumpExact jumpSameSign convert |
  	<var: #convert type: #'AbstractInstruction *'>
+ 	<var: #jumpIsSI type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpExact type: #'AbstractInstruction *'>
  	<var: #jumpSameSign type: #'AbstractInstruction *'>
  	self genLoadArgAtDepth: 0 into: TempReg.
  	self MoveR: TempReg R: ClassReg.
  	self MoveR: TempReg R: Arg1Reg.
  	jumpNotSI := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	"We must shift away the tags, not just subtract them, so that the
  	 overflow case doesn't actually overflow the machine instruction."
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: ClassReg].
  	jumpZero := self JumpZero: 0.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"If remainder is zero we must check for overflow."
  	self CmpCq: 0 R: ClassReg.
  	jumpExact := self JumpZero: 0.
  	"If arg and remainder signs are different we must round down."
  	self XorR: ClassReg R: Arg1Reg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: Arg1Reg].
  	jumpSameSign := self JumpGreaterOrEqual: 0.
  	self SubCq: 1 R: TempReg.
  	jumpSameSign jmpTarget: (convert := self Label).
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: (self primRetNOffsetFor: 1).
  	"test for overflow; the only case is SmallInteger minVal // -1"
+ 	jumpExact jmpTarget: self Label.
+ 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
+ 	jumpIsSI jmpTarget: convert.
- 	jumpExact jmpTarget:
- 		(self CmpCq: (1 << (objectRepresentation numSmallIntegerBits - 1)) R: TempReg).
- 	self JumpLess: convert.
  	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genPrimitiveDiv (in category 'primitive generators') -----
  genPrimitiveDiv
+ 	| jumpNotSI jumpIsSI jumpZero jumpExact jumpSameSign convert |
- 	| jumpNotSI jumpZero jumpExact jumpSameSign convert |
  	<var: #convert type: #'AbstractInstruction *'>
+ 	<var: #jumpIsSI type: #'AbstractInstruction *'>
  	<var: #jumpZero type: #'AbstractInstruction *'>
  	<var: #jumpNotSI type: #'AbstractInstruction *'>
  	<var: #jumpExact type: #'AbstractInstruction *'>
  	<var: #jumpSameSign type: #'AbstractInstruction *'>
  	self MoveR: Arg0Reg R: ClassReg.
  	self MoveR: Arg0Reg R: Arg1Reg.
  	jumpNotSI := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	"We must shift away the tags, not just subtract them, so that the
  	 overflow case doesn't actually overflow the machine instruction."
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: ClassReg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: ClassReg].
  	jumpZero := self JumpZero: 0.
  	self MoveR: ReceiverResultReg R: TempReg.
  	objectRepresentation genShiftAwaySmallIntegerTagsInScratchReg: TempReg.
  	self DivR: ClassReg R: TempReg Quo: TempReg Rem: ClassReg.
  	"If remainder is zero we must check for overflow."
  	self CmpCq: 0 R: ClassReg.
  	jumpExact := self JumpZero: 0.
  	"If arg and remainder signs are different we must round down."
  	self XorR: ClassReg R: Arg1Reg.
  	(self lastOpcode setsConditionCodesFor: JumpZero) ifFalse:
  		[self CmpCq: 0 R: Arg1Reg].
  	jumpSameSign := self JumpGreaterOrEqual: 0.
  	self SubCq: 1 R: TempReg.
  	jumpSameSign jmpTarget: (convert := self Label).
  	objectRepresentation genConvertIntegerToSmallIntegerInReg: TempReg.
  	self MoveR: TempReg R: ReceiverResultReg.
  	self RetN: 0.
  	"test for overflow; the only case is SmallInteger minVal // -1"
+ 	jumpExact jmpTarget: self Label.
+ 	jumpIsSI := objectRepresentation genJumpIsSmallIntegerValue: TempReg scratch: Arg1Reg.
+ 	jumpIsSI jmpTarget: convert.
- 	jumpExact jmpTarget:
- 		(self CmpCq: (1 << (objectRepresentation numSmallIntegerBits - 1)) R: TempReg).
- 	self JumpLess: convert.
  	jumpZero jmpTarget: (jumpNotSI jmpTarget: self Label).
  	^0!



More information about the Vm-dev mailing list