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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 31 21:28:33 UTC 2016


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

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

Name: VMMaker.oscog-eem.1755
Author: eem
Time: 1 January 1970, 2:26:33.237515 pm
UUID: adcfc67f-a856-48b8-aef2-71ff6275a903
Ancestors: VMMaker.oscog-nice.1754

Spur Cogit:
Add a compile-time flag, CheckRememberedInTrampoline, that controls whether the remembered check is generated in-line or in the trampoline.  If checked in the trampoline and on 64-bits use one memory access to get the header and share the access between the IMMUTABILITY check and the rememberedBit check.  Factor out the rememberedBit check into its own method.

The default leaves the code unchanged.  I doubt that the option will improve anything significantly; measuring the generated code in the simulator the option saves only 0.6% of generated code.  But it's so lovely being able to explore the question in a couple of hours instead of at least a day or two in C.

Here's the data: CRIT=CheckRememberedInTrampoline; this methid is the last method generated in a listener image before it prompts the user:
IMMTABILITY: 	16r93F80 <->    16r940E8: method:   16rC582F8 prim 117 selector:   16r6D12C8 primRead:into:startingAt:count:
IMMTABILICRIT: 	16r93250 <->    16r933B8: method:   16rC582F8 prim 117 selector:   16r6D12C8 primRead:into:startingAt:count:
VANILLA:		16r91C00 <->    16r91D68: method:   16rC582F8 prim 117 selector:   16r6D12C8 primRead:into:startingAt:count:
VANILLACRIT:	16r90D80 <->    16r90EE8: method:   16rC582F8 prim 117 selector:   16r6D12C8 primRead:into:startingAt:count:
16r93F80 - 16r93250 / 16r93250 * 100.0 0.5601422920704027
16r91C00 - 16r90D80 / 16r90D80 * 100.0 0.6256742179072277

And interestingly IMMUTABILITY adds only 1.5% to the code bulk; writes are rare.
16r93F80 - 16r91C00 / 16r91C00 * 100.0 1.5222984562607205
16r93250 - 16r90D80 / 16r90D80 * 100.0 1.5884573894282634

=============== Diff against VMMaker.oscog-nice.1754 ===============

Item was added:
+ ----- Method: CogObjectRepresentation class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 	"Override to avoid inheriting (and hence repeating) VMClass class>>initializeMiscConstants.
+ 	 Subclasses that have misc constants to initialize will override further."!

Item was changed:
  CogObjectRepresentation subclass: #CogObjectRepresentationForSpur
  	instanceVariableNames: 'ceScheduleScavengeTrampoline ceSmallActiveContextInMethodTrampoline ceSmallActiveContextInBlockTrampoline ceLargeActiveContextInMethodTrampoline ceLargeActiveContextInBlockTrampoline ceStoreCheckContextReceiverTrampoline ceStoreTrampolines'
+ 	classVariableNames: 'CheckRememberedInTrampoline NumStoreTrampolines'
- 	classVariableNames: 'NumStoreTrampolines'
  	poolDictionaries: 'VMBytecodeConstants VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur class>>initializeMiscConstants (in category 'initialization') -----
+ initializeMiscConstants
+ 	CheckRememberedInTrampoline := initializationOptions at: #CheckRememberedInTrampoline ifAbsent: [false]!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genCheckRememberedBitOf:scratch: (in category 'compile abstract instructions') -----
+ genCheckRememberedBitOf: objReg scratch: scratchReg
+ 	"Check the remembered bit of the object in objReg; answer the jump taken if the bit is already set.
+ 	 Only need to fetch the byte containing it, which reduces the size of the mask constant."
+ 	| rememberedBitByteOffset mask |
+ 	rememberedBitByteOffset := cogit backEnd isBigEndian
+ 									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
+ 									ifFalse:[objectMemory rememberedBitShift // 8].
+ 	mask := 1 << (objectMemory rememberedBitShift \\ 8).
+ 	cogit MoveMb: rememberedBitByteOffset r: objReg R: scratchReg.
+ 	cogit TstCq: mask R: scratchReg.
+ 	^cogit JumpNonZero: 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreCheckReceiverReg:valueReg:scratchReg:inFrame: (in category 'compile abstract instructions') -----
  genStoreCheckReceiverReg: destReg valueReg: valueReg scratchReg: scratchReg inFrame: inFrame
  	"Generate the code for a store check of valueReg into destReg."
+ 	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered |
- 	| jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered mask rememberedBitByteOffset |
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  	"Is value stored an immediate?  If so we're done"
  	jmpImmediate := self genJumpImmediate: valueReg.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: valueReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
+ 	 Need to remember this only if the remembered bit is not already set."
+ 	CheckRememberedInTrampoline ifFalse:
+ 		[jmpAlreadyRemembered := self genCheckRememberedBitOf: destReg scratch: scratchReg].
- 	 Need to remember this only if the remembered bit is not already set.
- 	 Test the remembered bit.  Only need to fetch the byte containing it,
- 	 which reduces the size of the mask constant."
- 	rememberedBitByteOffset := jmpSourceOld isBigEndian
- 									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
- 									ifFalse:[objectMemory rememberedBitShift // 8].
- 	mask := 1 << (objectMemory rememberedBitShift \\ 8).
- 	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
- 	cogit AndCq: mask R: scratchReg.
- 	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Remembered bit is not set.  Call store check to insert dest into remembered table."
  	self assert: destReg = ReceiverResultReg.
  	cogit 
  		evaluateTrampolineCallBlock: [cogit CallRT: ceStoreCheckTrampoline]
  		protectLinkRegIfNot: inFrame.
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
+ 		cogit Label)).
+ 	CheckRememberedInTrampoline ifFalse:
+ 		[jmpAlreadyRemembered jmpTarget: jmpSourceOld getJmpTarget].
- 	(jmpAlreadyRemembered jmpTarget:
- 		cogit Label))).
  	^0!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>genStoreCheckTrampoline (in category 'initialization') -----
+ genStoreCheckTrampoline
+ 	| jumpSC |
+ 	<var: #jumpSC type: #'AbstractInstruction *'>
+ 	<inline: true>
+ 	CheckRememberedInTrampoline ifTrue:
+ 		[cogit zeroOpcodeIndex.
+ 		 jumpSC := self genCheckRememberedBitOf: ReceiverResultReg scratch: cogit backEnd cResultRegister.
+ 		 self assert: jumpSC opcode = JumpNonZero.
+ 		 jumpSC opcode: JumpZero.
+ 		 cogit RetN: 0.
+ 		 jumpSC jmpTarget: cogit Label].
+ 	^cogit
+ 		genTrampolineFor: #remember:
+ 		called: 'ceStoreCheckTrampoline'
+ 		numArgs: 1
+ 		arg: ReceiverResultReg
+ 		arg: nil
+ 		arg: nil
+ 		arg: nil
+ 		regsToSave: (cogit callerSavedRegMask bitClear: (cogit registerMaskFor: ReceiverResultReg))
+ 		pushLinkReg: true
+ 		resultReg: cogit returnRegForStoreCheck
+ 		appendOpcodes: CheckRememberedInTrampoline!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreTrampolineCalled:instVarIndex: (in category 'initialization') -----
  genStoreTrampolineCalled: trampolineName instVarIndex: instVarIndex
  	"Convention:
  	- RcvrResultReg holds the object mutated.
  	If immutability failure:
  	- TempReg holds the instance variable index mutated 
  		if instVarIndex > numDedicatedStoreTrampoline
  	- ClassReg holds the value to store
  	Registers are not lived across this trampoline as the 
  	immutability failure may need new stack frames."
  	
+ 	| jumpSC jumpRC |
- 	| jumpSC |
  	<option: #IMMUTABILITY>
  	<var: #trampolineName type: #'char *'>
  	<var: #jumpSC type: #'AbstractInstruction *'>
+ 	<var: #jumpRC type: #'AbstractInstruction *'>
  	<inline: false>
  	cogit zeroOpcodeIndex.
  	"SendNumArgsReg is mutated but we don't care as register are not live across the trampoline.
  	 There is no reason why registers cannot be saved over the remember: call, but since the
  	 immutability check is a suspension point, registers cannot remain live."
  	jumpSC := self genJumpMutable: ReceiverResultReg scratchReg: SendNumArgsReg.
  	cogit
  		compileTrampolineFor: #ceCannotAssignTo:withIndex:valueToAssign:
  		numArgs: 3
  		arg: ReceiverResultReg
  		arg: (instVarIndex < (NumStoreTrampolines - 1)
  				ifTrue: [cogit trampolineArgConstant: instVarIndex]
  				ifFalse: [TempReg])
  		arg: ClassReg
  		arg: nil
  		regsToSave: cogit emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg.
  		
  	"Store check"
  	jumpSC jmpTarget: cogit Label.
+ 	"If on 64-bits and doing the remembered bit test here, we can combine the tests to fetch the header once."
+ 	CheckRememberedInTrampoline ifTrue:
+ 		[objectMemory wordSize = 8
+ 			ifTrue:
+ 				[cogit TstCq: 1 << objectMemory rememberedBitShift R: SendNumArgsReg.
+ 				 jumpRC := cogit JumpZero: 0.
+ 				 cogit RetN: 0]
+ 			ifFalse:
+ 				[jumpRC := self genCheckRememberedBitOf: ReceiverResultReg scratch: SendNumArgsReg.
+ 				 self assert: jumpRC opcode = JumpNonZero.
+ 				 jumpRC opcode: JumpZero.
+ 				 cogit RetN: 0].
+ 		 jumpRC jmpTarget: cogit Label].
  	^ cogit genTrampolineFor: #remember:
  		called: trampolineName
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		regsToSave: cogit emptyRegisterMask
  		pushLinkReg: true
  		resultReg: NoReg
  		appendOpcodes: true!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityAndStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needRestoreRcvr: needRestoreRcvr 
  	"Store check code is duplicated to use a single trampoline"
+ 	| immutableJump jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered |
- 	| immutableJump jmpImmediate jmpDestYoung jmpSourceOld rememberedBitByteOffset jmpAlreadyRemembered mask |
  	<var: #immutableJump type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  
  	immutableJump := self genJumpImmutable: destReg scratchReg: scratchReg.
  	
  	cogit genTraceStores.
  	
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  	
  	"store check"
  	jmpImmediate := self genJumpImmediate: sourceReg.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
+ 	 Need to remember this only if the remembered bit is not already set."
+ 	CheckRememberedInTrampoline ifFalse:
+ 		[jmpAlreadyRemembered := self genCheckRememberedBitOf: destReg scratch: scratchReg].
- 	 Need to remember this only if the remembered bit is not already set.
- 	 Test the remembered bit.  Only need to fetch the byte containing it,
- 	 which reduces the size of the mask constant."
- 	rememberedBitByteOffset := jmpSourceOld isBigEndian
- 									ifTrue: [objectMemory baseHeaderSize - 1 - (objectMemory rememberedBitShift // 8)]
- 									ifFalse:[objectMemory rememberedBitShift // 8].
- 	mask := 1 << (objectMemory rememberedBitShift \\ 8).
- 	cogit MoveMb: rememberedBitByteOffset r: destReg R: scratchReg.
- 	cogit AndCq: mask R: scratchReg.
- 	jmpAlreadyRemembered := cogit JumpNonZero: 0.
  	"Set the inst var index for the benefit of the immutability check. The trampoline will
  	 repeat the check to choose between the immutbality violation and the store check."
  	immutableJump jmpTarget: cogit Label.
  	self genStoreTrampolineCall: index.
  	needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
  
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
+ 		cogit Label)).
+ 	CheckRememberedInTrampoline ifFalse:
+ 		[jmpAlreadyRemembered jmpTarget: jmpSourceOld getJmpTarget].
- 	(jmpAlreadyRemembered jmpTarget:
- 		cogit Label))).
- 	
  	^ 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>generateObjectRepresentationTrampolines (in category 'initialization') -----
  generateObjectRepresentationTrampolines
  	"Do the store check.  Answer the argument for the benefit of the code generator;
  	 ReceiverResultReg may be caller-saved and hence smashed by this call.  Answering
  	 it allows the code generator to reload ReceiverResultReg cheaply.
  	 In Spur the only thing we leave to the run-time is adding the receiver to the
  	 remembered set and setting its isRemembered bit."
  	self 
  		cppIf: IMMUTABILITY
  		ifTrue: 
  			[self cCode: [] inSmalltalk:
  				[ceStoreTrampolines := CArrayAccessor on: (Array new: NumStoreTrampolines)].
  			 0 to: NumStoreTrampolines - 1 do:
  				[:instVarIndex |
  				 ceStoreTrampolines
  					at: instVarIndex
  					put: (self 
  							genStoreTrampolineCalled: (cogit 
  															trampolineName: 'ceStoreTrampoline' 
  															numArgs: instVarIndex 
  															limit: NumStoreTrampolines - 2) 
  							instVarIndex: instVarIndex)]].
+ 	ceStoreCheckTrampoline := self genStoreCheckTrampoline.
- 	ceStoreCheckTrampoline := cogit
- 									genTrampolineFor: #remember:
- 									called: 'ceStoreCheckTrampoline'
- 									arg: ReceiverResultReg
- 									regsToSave: (cogit callerSavedRegMask bitClear: (cogit registerMaskFor: ReceiverResultReg))
- 									result: cogit returnRegForStoreCheck.
  	ceStoreCheckContextReceiverTrampoline := self genStoreCheckContextReceiverTrampoline.
  	ceScheduleScavengeTrampoline := cogit
  											genTrampolineFor: #ceScheduleScavenge
  											called: 'ceScheduleScavengeTrampoline'
  											regsToSave: cogit callerSavedRegMask.
  	ceSmallActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: false inBlock: false called: 'ceSmallMethodContext'.
  	ceSmallActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: false inBlock: true called: 'ceSmallBlockContext'.
  	ceLargeActiveContextInMethodTrampoline := self genActiveContextTrampolineLarge: true inBlock: false called: 'ceLargeMethodContext'.
  	ceLargeActiveContextInBlockTrampoline := self genActiveContextTrampolineLarge: true inBlock: true called: 'ceLargeBlockContext'!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := initializationOptions at: #Debug ifAbsent: [false].
  	(initializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := initializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (initializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
  							[#X64] 		->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
  	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
  		[:compilerClass| compilerClass initialize; initializeAbstractRegisters].
+ 	self objectMemoryClass objectRepresentationClass initializeMiscConstants.
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := initializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
  	"Answer the set of names for variables that should be defined at compile time.
  	 Some of these get default values during simulation, and hence get defaulted in
  	 the various initializeMiscConstants methods.  But that they have values should
  	 /not/ cause the code generator to do dead code elimination based on their
  	 default values."
  	^#(	VMBIGENDIAN
  		IMMUTABILITY
  		STACKVM COGVM COGMTVM SPURVM
+ 		PharoVM								"Pharo vs Squeak"
+ 		EnforceAccessControl					"Newspeak"
+ 		CheckRememberedInTrampoline)		"IMMUTABILITY"!
- 		"Pharo vs Squeak" PharoVM
- 		"Newspeak" EnforceAccessControl)!



More information about the Vm-dev mailing list