[Vm-dev] VM Maker: VMMaker.oscog-cb.1814.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 18 15:49:00 UTC 2016


ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.1814.mcz

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

Name: VMMaker.oscog-cb.1814
Author: cb
Time: 18 April 2016, 8:47:19.742585 am
UUID: 9071cb14-5130-4cfa-bc91-324ea4eded36
Ancestors: VMMaker.oscog-cb.1813

- added cogit to BytecodeFixup for slang style double dispatch.
- improved support for register allocation: branch merge successfully compiled with register moved instead of spilling.
- added convenient API for simStack printing to debug 
- started to fix liveRegister liveness.

=============== Diff against VMMaker.oscog-cb.1813 ===============

Item was added:
+ ----- Method: CogBytecodeFixup class>>for: (in category 'instance creation') -----
+ for: aCogit
+ 	^self new!

Item was changed:
  CogSSBytecodeFixup subclass: #CogRASSBytecodeFixup
+ 	instanceVariableNames: 'cogit mergeSimStack'
- 	instanceVariableNames: 'mergeSimStack'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogRASSBytecodeFixup class>>for: (in category 'instance creation') -----
+ for: aCogit
+ 	^self new cogit: aCogit!

Item was changed:
  ----- Method: CogRASSBytecodeFixup class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogRASSBytecodeFixup struct."
  
+ 	(self allInstVarNames copyWithout: 'cogit') do:
- 	self allInstVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
  					['targetInstruction']	-> [#'AbstractInstruction *'].
  					['mergeSimStack']	-> [#'CogSimStackEntry *'] }
  					otherwise: [#sqInt])]!

Item was added:
+ ----- Method: CogRASSBytecodeFixup>>cogit: (in category 'initialize-release') -----
+ cogit: aCogit
+ 	cogit := aCogit.
+ 	^self!

Item was added:
+ ----- Method: CogRASSBytecodeFixup>>printMergeSimStack (in category 'debug printing') -----
+ printMergeSimStack
+ 	<doNotGenerate>
+ 	self notAFixup ifFalse:
+ 		[cogit printSimStack: mergeSimStack toDepth: simStackPtr spillBase: -1]!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes
  	"Allocate the various arrays needed to compile abstract instructions.
  	 Notionally we only need as many fixups as there are bytecodes.  But we
  	 reuse fixups to record pc-dependent instructions in generateInstructionsAt:
  	 and so need at least as many as there are abstract opcodes.
  
  	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
  	 so that they are freed when compilation is done.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<inline: true>
  	numAbstractOpcodes := numberOfAbstractOpcodes.
  	self
  		cCode:
  			[| opcodeSize fixupSize|
  			 opcodeSize := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
  			 fixupSize := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
  			 abstractOpcodes := self alloca: opcodeSize + fixupSize.
  			 self b: abstractOpcodes zero: opcodeSize + fixupSize.
  			 fixups := (abstractOpcodes asUnsignedInteger + opcodeSize) asVoidPointer]
  		inSmalltalk:
  			[abstractOpcodes := CArrayAccessor on:
  									 ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
  			 fixups := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass for: self])].
- 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass new])].
  	self zeroOpcodeIndex.
  	labelCounter := 0!

Item was changed:
  ----- Method: Cogit>>allocateOpcodes:bytecodes:ifFail: (in category 'initialization') -----
  allocateOpcodes: numberOfAbstractOpcodes bytecodes: numberOfBytecodes ifFail: failBlock
  	"Allocate the various arrays needed to compile abstract instructions, failing if the size
  	 needed is considered too high.  Notionally we only need as many fixups as there are
  	 bytecodes.  But we reuse fixups to record pc-dependent instructions in
  	 generateInstructionsAt: and so need at least as many as there are abstract opcodes.
  
  	 This *must* be inlined since the arrays are alloca'ed (stack allocated)
  	 so that they are freed when compilation is done.
  
  	 N.B. We do one single alloca to save embarrassing C optimizers that
  	 generate incorrect code as both gcc and the intel compiler do on x86."
  	<inline: true>
  	| opcodeBytes fixupBytes allocBytes |
  	numAbstractOpcodes := numberOfAbstractOpcodes.
  	opcodeBytes := (self sizeof: CogAbstractInstruction) * numAbstractOpcodes.
  	fixupBytes := (self sizeof: CogBytecodeFixup) * numAbstractOpcodes.
  	allocBytes := opcodeBytes + fixupBytes.
  	allocBytes > MaxStackAllocSize ifTrue: [^failBlock value].
  	self
  		cCode:
  			[abstractOpcodes := self alloca: allocBytes.
  			 self b: abstractOpcodes zero: allocBytes.
  			 fixups := (abstractOpcodes asUnsignedInteger + opcodeBytes) asVoidPointer]
  		inSmalltalk:
  			[abstractOpcodes := CArrayAccessor on:
  									 ((1 to: numAbstractOpcodes) collect: [:ign| CogCompilerClass for: self]).
  			 fixups := CArrayAccessor on:
+ 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass for: self])].
- 						((1 to: numAbstractOpcodes) collect: [:ign| self bytecodeFixupClass new])].
  	self zeroOpcodeIndex.
  	labelCounter := 0!

Item was removed:
- ----- Method: RegisterAllocatingCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
- genJumpIf: boolean to: targetBytecodePC
- 	<inline: false>
- 	| desc fixup ok |
- 	<var: #desc type: #'CogSimStackEntry *'>
- 	<var: #fixup type: #'BytecodeFixup *'>
- 	<var: #ok type: #'AbstractInstruction *'>
- 	1halt.
- 	self ssFlushTo: simStackPtr - 1.
- 	desc := self ssTop.
- 	self ssPop: 1.
- 	(desc type == SSConstant
- 	 and: [desc constant = objectMemory trueObject or: [desc constant = objectMemory falseObject]]) ifTrue:
- 		["Must arrange there's a fixup at the target whether it is jumped to or
- 		  not so that the simStackPtr can be kept correct."
- 		 fixup := self ensureFixupAt: targetBytecodePC - initialPC.
- 		 "Must enter any annotatedConstants into the map"
- 		 desc annotateUse ifTrue:
- 			[self annotateBytecode: (self prevInstIsPCAnnotated
- 											ifTrue: [self Nop]
- 											ifFalse: [self Label])].
- 		 "Must annotate the bytecode for correct pc mapping."
- 		 self annotateBytecode: (desc constant = boolean
- 									ifTrue: [self Jump: fixup]
- 									ifFalse: [self prevInstIsPCAnnotated
- 												ifTrue: [self Nop]
- 												ifFalse: [self Label]]).
- 		 ^0].
- 	desc popToReg: TempReg.
- 	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
- 	 Correct result is either 0 or the distance between them.  If result is not 0 or
- 	 their distance send mustBeBoolean."
- 	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
- 	self genSubConstant: boolean R: TempReg.
- 	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
- 
- 	self extASpecifiesNoMustBeBoolean ifTrue: 
- 		[ extA := 0. 
- 		self annotateBytecode: self lastOpcode.
- 		^ 0].
- 	extA := 0.
- 	
- .	self CmpCq: (boolean == objectMemory falseObject
- 					ifTrue: [objectMemory trueObject - objectMemory falseObject]
- 					ifFalse: [objectMemory falseObject - objectMemory trueObject])
- 		R: TempReg.
- 	ok := self JumpZero: 0.
- 	self CallRT: (boolean == objectMemory falseObject
- 					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
- 					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
- 	ok jmpTarget: (self annotateBytecode: self Label).
- 	^0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>genJumpTo: (in category 'bytecode generator support') -----
  genJumpTo: targetBytecodePC
+ 	"Overriden to avoid the flush because in this cogit stack state is merged at merge point."
+ 	deadCode := true. "can't fall through"
  	self Jump: (self ensureFixupAt: targetBytecodePC - initialPC).
  	^ 0!

Item was changed:
  ----- Method: RegisterAllocatingCogit>>mergeCurrentSimStackWith: (in category 'bytecode generator support') -----
  mergeCurrentSimStackWith: mergeSimStack
  	<var: #mergeSimStack type: #'SimStackEntry *'>
  	<var: #currentSSEntry type: #'SimStackEntry *'>
  	<var: #expectedSSEntry type: #'SimStackEntry *'>
  	"At merge point the cogit expects the stack to be in the same state as mergeSimStack.
  	The logic is very naive, we align the existing state from the current stack to the merge stack
  	from simStackPtr to methodOrBlockNumTemps, and if a conflict happen, we flush what remains
  	to be merged."
  	self flag: #TODO. "we could have a better algorithm with the current set of live registers to avoid flushing"
+ 	1halt.
  	simStackPtr to: methodOrBlockNumTemps by: -1 do:
  		[:i|
  			| currentSSEntry expectedSSEntry |
  			currentSSEntry := self simStackAt: i.
  			expectedSSEntry := self simStack: mergeSimStack at: i.
+ 			expectedSSEntry type
- 			expectedSSEntry
  				caseOf: {
  					[SSBaseOffset]	-> [ self assert: (expectedSSEntry register = ReceiverResultReg or: [ expectedSSEntry register = FPReg ]).
  										(expectedSSEntry register = ReceiverResultReg and: [needsFrame]) ifTrue: 
  											[optStatus isReceiverResultRegLive ifFalse: 
  												[self ssFlushFrom: i - 1 upThroughRegister: ReceiverResultReg.
  											 	 self putSelfInReceiverResultReg ].
  											 optStatus isReceiverResultRegLive: true].  ].
  					[SSSpill]		-> [currentSSEntry ensureSpilledAt: (self frameOffsetOfTemporary: i) from: FPReg].
  					[SSConstant]	-> [self assert: expectedSSEntry liveRegister notNil. 
  										currentSSEntry storeToReg: expectedSSEntry liveRegister ].
  					[SSRegister]	-> [(currentSSEntry type = SSRegister and: [currentSSEntry register = expectedSSEntry register])
  											ifFalse: 
  												[ self ssFlushFrom: i - 1 upThroughRegister: expectedSSEntry register.
  												currentSSEntry storeToReg: expectedSSEntry register ] ]}.
  			 ]!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>mergeWithFixupIfRequired: (in category 'simulation stack') -----
+ mergeWithFixupIfRequired: fixup
+ 	"If this bytecode has a fixup, some kind of merge needs to be done. There are 4 cases:
+ 		1) the bytecode has no fixup (fixup isNotAFixup)
+ 			do nothing
+ 		2) the bytecode has a non merge fixup
+ 			the fixup has needsNonMergeFixup.
+ 			The code generating non merge fixup (currently only special selector code) is responsible
+ 				for the merge so no need to do it.
+ 			We set deadCode to false as the instruction can be reached from jumps.
+ 		3) the bytecode has a merge fixup, but execution flow *cannot* fall through to the merge point.
+ 			the fixup has needsMergeFixup and deadCode = true.
+ 			ignores the current simStack as it does not mean anything 
+ 			restores the simStack to the state the jumps to the merge point expects it to be.
+ 		4) the bytecode has a merge fixup and execution flow *can* fall through to the merge point.
+ 			the fixup has needsMergeFixup and deadCode = false.
+ 			flushes the stack to the stack pointer so the fall through execution path simStack is 
+ 				in the state the merge point expects it to be. 
+ 			restores the simStack to the state the jumps to the merge point expects it to be.
+ 			
+ 	In addition, if this is a backjump merge point, we patch the fixup to hold the current simStackPtr 
+ 	for later assertions."
+ 	
+ 	<var: #fixup type: #'BytecodeFixup *'>
+ 	"case 1"
+ 	fixup notAFixup ifTrue: [^ 0].
+ 
+ 	"case 2"
+ 	fixup isNonMergeFixup ifTrue: [deadCode := false. ^ 0 ].
+ 
+ 	"cases 3 and 4"
+ 	1halt.
+ 	self assert: fixup isMergeFixup.
+ 	self traceMerge: fixup.
+ 	deadCode 
+ 		ifTrue: [simStackPtr := fixup simStackPtr] "case 3"
+ 		ifFalse: [self mergeCurrentSimStackWith: fixup mergeSimStack]. "case 4"
+ 	"cases 3 and 4"
+ 	deadCode := false.
+ 	fixup isBackwardBranchFixup ifTrue: [fixup simStackPtr: simStackPtr].
+ 	fixup targetInstruction: self Label.
+ 	self assert: simStackPtr = fixup simStackPtr.
+ 	self cCode: '' inSmalltalk:
+ 		[self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].
+ 	self restoreSimStackAtMergePoint: fixup.
+ 	
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>restoreSimStackAtMergePoint: (in category 'simulation stack') -----
+ restoreSimStackAtMergePoint: fixup
+ 	<inline: true>
+ 	"All the execution paths reaching a merge point expect everything to be
+ 	spilled on stack and the optStatus is unknown. Throw away all simStack and 
+ 	optStatus optimization state."
+ 	simSpillBase := methodOrBlockNumTemps.
+ 	optStatus isReceiverResultRegLive: false.
+ 	0 to: simStackPtr do:
+ 		[:i|
+ 		self cCode: [simStack at: i put: (fixup mergeSimStack at: i)]
+ 			inSmalltalk: [(simStack at: i) copyFrom: (fixup mergeSimStack at: i)]].
+ 	^ 0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>ssPushAnnotatedConstant: (in category 'simulation stack') -----
+ ssPushAnnotatedConstant: literal
+ 	super ssPushAnnotatedConstant: literal.
+ 	self ssTop liveRegister: NoReg.
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>ssPushBase:offset: (in category 'simulation stack') -----
+ ssPushBase: reg offset: offset
+ 	super ssPushBase: reg offset: offset.
+ 	self ssTop liveRegister: NoReg.
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>ssPushConstant: (in category 'simulation stack') -----
+ ssPushConstant: literal
+ 	super ssPushConstant: literal.
+ 	self ssTop liveRegister: NoReg.
+ 	^0!

Item was added:
+ ----- Method: RegisterAllocatingCogit>>ssPushRegister: (in category 'simulation stack') -----
+ ssPushRegister: reg
+ 	super ssPushRegister: reg.
+ 	self ssTop liveRegister: NoReg.
+ 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>printSimStack (in category 'simulation only') -----
  printSimStack
  	<doNotGenerate>
+ 	self printSimStack: simStack toDepth: simStackPtr spillBase: simSpillBase!
- 	coInterpreter transcript ensureCr.
- 	simStackPtr < 0 ifTrue:
- 		[^coInterpreter transcript nextPutAll: 'simStackEmpty'; cr; flush].
- 	0 to: simStackPtr do:
- 		[:i|
- 		coInterpreter transcript print: i.
- 		i = simSpillBase
- 			ifTrue: [coInterpreter transcript nextPutAll: ' sb'; tab]
- 			ifFalse: [coInterpreter transcript tab; tab].
- 		(simStack at: i) printStateOn: coInterpreter transcript.
- 		coInterpreter transcript cr; flush]!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>printSimStack:toDepth:spillBase: (in category 'simulation only') -----
+ printSimStack: aSimStack toDepth: limit spillBase: spillBase
+ 	<doNotGenerate>
+ 	coInterpreter transcript ensureCr.
+ 	limit < 0 ifTrue:
+ 		[^coInterpreter transcript nextPutAll: 'simStackEmpty'; cr; flush].
+ 	0 to: limit do:
+ 		[:i|
+ 		coInterpreter transcript print: i.
+ 		i = spillBase
+ 			ifTrue: [coInterpreter transcript nextPutAll: ' sb'; tab]
+ 			ifFalse: [coInterpreter transcript tab; tab].
+ 		(aSimStack at: i) printStateOn: coInterpreter transcript.
+ 		coInterpreter transcript cr; flush]!



More information about the Vm-dev mailing list