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

commits at source.squeak.org commits at source.squeak.org
Fri Feb 2 20:59:22 UTC 2018


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

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

Name: VMMaker.oscog-eem.2328
Author: eem
Time: 2 February 2018, 12:58:43.151351 pm
UUID: 38b7b2c3-c420-4a1b-b83a-44f6fbbfea0d
Ancestors: VMMaker.oscog-eem.2327

StackToRegisterMappingCogit:
Replace the UnknownSimStackPtrFlag hack in a fixup's simStackPtr and replace it by a proper flag.  Consequently make a fixup's simStackPtr unsigned char, giving us a maximim of 255 stack slots (0 being for the receiver).

Fix typos and remove unnecessary doNotGenerate's from initialize methods (CCodeGenerator filters inityialize methods out anyway).

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

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		["only remove a previous method if this one overrides it, i.e. this is a subclass method.
  		 If the existing method is in a different hierarchy this method must be merely a redeirect."
  		 (methods at: selector ifAbsent: []) ifNotNil:
  			[:tm|
  			(aClass includesBehavior: tm definingClass) ifTrue:
  				[self removeMethodForSelector: selector]].
  		 ^nil].
  	method isSubclassResponsibility ifTrue:
  		[^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[^nil].
  	tmethod := self compileToTMethodSelector: selector in: aClass.
+ 	"Even though we exclude initialize methods, we must consider their
- 	"Even thoug we exclude initialize methods, we must consider their
  	 global variable usage, otherwise globals may be incorrectly localized."
  	selector == #initialize ifTrue:
  		[self checkForGlobalUsage: (tmethod allReferencedVariablesUsing: self) in: tmethod.
  		 ^nil].
  	self addMethod: tmethod.
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	(method pragmaAt: #cmacro) ifNotNil:
  		[:pragma| | literal | "Method should be just foo ^const"
  		self assert: (method numArgs = 0 and: [method numLiterals = 3 or: [method isQuick]]).
  		literal := method isQuick
  					ifTrue: [method decompile block statements last expr key]
  					ifFalse: [method literalAt: 1].
  		self addMacro: '() ', (method isReturnField
  								ifTrue: [literal]
  								ifFalse: [self cLiteralFor: literal value name: method selector]) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	^tmethod!

Item was changed:
  ----- Method: CoInterpreterMT>>initialize (in category 'initialization') -----
  initialize
- 	<doNotGenerate>
  	super initialize.
  	relinquishing := checkThreadActivation := deferThreadSwitch := false.
  	foreignCallbackPriority := maxWaitingPriority := disownCount := willNotThreadWarnCount := 0!

Item was changed:
  SharedPool subclass: #CogAbstractRegisters
  	instanceVariableNames: ''
+ 	classVariableNames: 'Arg0Reg Arg1Reg CallerSavedRegisterMask ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg FPReg LinkReg NoReg NumFloatRegisters NumRegisters PCReg RISCTempReg ReceiverResultReg SPReg SendNumArgsReg TempReg VarBaseReg'
- 	classVariableNames: 'Arg0Reg Arg1Reg CallerSavedRegisterMask ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg FPReg LinkReg NoReg PCReg RISCTempReg ReceiverResultReg SPReg SendNumArgsReg TempReg VarBaseReg'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogAbstractRegisters commentStamp: 'eem 12/26/2015 14:06' prior: 0!
  I am a pool for the abstract register set that the Cogit uses to define its model of Smalltalk compiled to machine code.!

Item was changed:
  ----- Method: CogBytecodeFixup class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"Enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a BytecodeFixup struct."
  	"self withAllSubclasses collect: [:ea| ea typedef]"
  
  	self filteredInstVarNames do:
  		[:ivn|
  		 aBinaryBlock
  			value: ivn
  			value: (ivn first ~= $# ifTrue:
  						[ivn caseOf: {
+ 							['targetInstruction']				-> [#'AbstractInstruction *'].
+ 							['mergeSimStack']				-> [#'SimStackEntry *'].
+ 							['instructionIndex']				-> [#'unsigned short'].
+ 							['simStackPtr']					-> [#'unsigned char'].
+ 							['simNativeStackPtr']			-> [#'short'].
+ 							['simNativeStackSize']			-> [#'unsigned short'].
+ 							['isTargetOfBackwardBranch']	-> [#char] }])]!
- 							['targetInstruction']			-> [#'AbstractInstruction *'].
- 							['mergeSimStack']			-> [#'SimStackEntry *'].
- 							['instructionIndex']			-> [#'unsigned short'].
- 							['simStackPtr']				-> [#'signed char'].
- 							['simNativeStackPtr']		-> [#'short'].
- 							['simNativeStackSize']		-> [#'unsigned short'].
- 							['isReceiverResultRegSelf']	-> [#char] }])]!

Item was changed:
+ ----- Method: CogBytecodeFixup>>initialize (in category 'instance initialization') -----
- ----- Method: CogBytecodeFixup>>initialize (in category 'initialize-release') -----
  initialize
- 	<doNotGenerate>
  	targetInstruction := 0!

Item was changed:
  ----- Method: CogRASSBytecodeFixup class>>filteredInstVarNames (in category 'translation') -----
  filteredInstVarNames
  	"Override to group char and short vars together for compactness.
  	 self typedef"
  	| vars |
  	vars := super filteredInstVarNames asOrderedCollection.
  	vars
  		remove: 'mergeSimStack';
+ 		add: 'mergeSimStack' afterIndex: (vars indexOf: 'targetInstruction').
- 		add: 'mergeSimStack' afterIndex: (vars indexOf: 'targetInstruction');
- 		remove: 'isReceiverResultRegSelf';
- 		add: 'isReceiverResultRegSelf' afterIndex: (vars indexOf: 'simStackPtr').
  	^vars!

Item was changed:
  CogBytecodeFixup subclass: #CogSSBytecodeFixup
+ 	instanceVariableNames: 'simStackPtr isTargetOfBackwardBranch simNativeStackPtr simNativeStackSize'
+ 	classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag'
- 	instanceVariableNames: 'simStackPtr simNativeStackPtr simNativeStackSize'
- 	classVariableNames: 'NeedsMergeFixupFlag NeedsNonMergeFixupFlag UnknownSimStackPtrFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
+ !CogSSBytecodeFixup commentStamp: 'eem 2/2/2018 10:51' prior: 0!
- !CogSSBytecodeFixup commentStamp: 'eem 11/22/2016 08:39' prior: 0!
  A CogSSBytecodeFixup extends CogBytecodeFixup with state to merge the stack at control-flow joins.  At a join the code generator must ensure that the stack is spilled to the same point along both branches and that the simStackPtr is correct.
  
  Instance Variables
+ 	simStackPtr:					<Integer>
+ 	isTargetOfBackwardBranch:		<Boolean>
- 	simStackPtr:		<Integer>
  
  simStackPtr
+ 	- the simStackPtr at the jump to this fixup.  It should either agree with the incoming fixup if control continues, or replace the simStackPtr if control doesn't continue (the incoming control flow ended with a return)
+ 
+ isTargetOfBackwardBranch:
+ 	- if true the fixup is the target of some backward branch!
- 	- the simStackPtr at the jump to this fixup.  It should either agree with the incoming fixup if control continues, or replace the simStackPtr if control doesn't continue (the incomming control flow ended with a return)!

Item was changed:
  ----- Method: CogSSBytecodeFixup class>>filteredInstVarNames (in category 'translation') -----
  filteredInstVarNames
  	"Override to add ifdef LowcodeVM around the native stack info, and to put
  	 char vars before short vars.
  	 self typedef"
  	| vars |
  	vars := super filteredInstVarNames asOrderedCollection.
  	vars
  		remove: 'instructionIndex';
+ 			add: 'instructionIndex' afterIndex: (vars indexOf: 'simStackPtr');
+ 		remove: 'isTargetOfBackwardBranch';
+ 			add: 'isTargetOfBackwardBranch' afterIndex: (vars indexOf: 'simStackPtr');
- 		add: 'instructionIndex' afterIndex: (vars indexOf: 'simStackPtr');
  		add: '#if LowcodeVM' beforeIndex: (vars indexOf: 'simNativeStackPtr');
  		add: '#endif' afterIndex: (vars indexOf: 'simNativeStackSize').
  	^vars!

Item was changed:
  ----- Method: CogSSBytecodeFixup class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize the fixup flags.  In this class we have two states.  A fixup is a bytecode
  	 being targeted by a branch, and a jump can target the fixup before the byetcode
  	 is generated.  A non-merge fixup is that for a bytecode that follows a return instruction.
  	 There is no control flow merge from the preceding instruction for this kind of fixup.
  	 A merge fixup is that for a bytecode where control flow arrives from both the preceding
  	 instruction and a branch.  When compileAbstractInstructionsFrom:to: finds a merge
  	 fixup, it must both set the targetInstruction and merge the stack/register state of the
  	 control flow from the preceding instruction with the stack/register state from the branch.
  	 Later still, when code is generated jumps follow fixups to eliminate the fixup and target
  	 the right instruction."
  	NeedsNonMergeFixupFlag := 1.
  	NeedsMergeFixupFlag := 2.
+ 	self assert: NeedsNonMergeFixupFlag < NeedsMergeFixupFlag!
- 	self assert: NeedsNonMergeFixupFlag < NeedsMergeFixupFlag.
- 
- 	UnknownSimStackPtrFlag := -2!

Item was added:
+ ----- Method: CogSSBytecodeFixup>>initialize (in category 'instance initialization') -----
+ initialize
+ 	targetInstruction := 0.
+ 	isTargetOfBackwardBranch := false!

Item was changed:
  ----- Method: CogSSBytecodeFixup>>isBackwardBranchFixup (in category 'testing') -----
  isBackwardBranchFixup
+ 	^isTargetOfBackwardBranch!
- 	<inline: true>
- 	^ simStackPtr = UnknownSimStackPtrFlag!

Item was changed:
  ----- Method: CogSSBytecodeFixup>>setIsBackwardBranchFixup (in category 'accessing') -----
  setIsBackwardBranchFixup
  	<inline: true>
+ 	isTargetOfBackwardBranch := true!
- 	simStackPtr := UnknownSimStackPtrFlag.
- 	LowcodeVM ifTrue: [ 
- 		simNativeStackPtr := UnknownSimStackPtrFlag.
- 		simNativeStackSize := 0.
- 	]
- !

Item was changed:
  ----- Method: NewObjectMemory>>initialize (in category 'initialization') -----
  initialize
- 	<doNotGenerate>
  	"Initialize NewObjectMemory when simulating the VM inside Smalltalk."
  	super initialize.
  	checkForLeaks := fullGCLock := 0.
  	needGCFlag := false.
  	heapMap := CogCheck32BitHeapMap new!

Item was changed:
  ----- Method: ObjectMemory>>initialize (in category 'initialization') -----
  initialize
- 	<doNotGenerate>
  	"Initialize ObjectMemory when simulating the VM inside Smalltalk."
  	super initialize.
  	headerTypeBytes := CArrayAccessor on: HeaderTypeExtraBytes.
  	rootTable := Array new: RootTableSize.
  	weakRoots := Array new: WeakRootTableSize.
  	remapBuffer := Array new: RemapBufferSize!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>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 *'>
  
  	self assertCorrectSimStackPtr.
  
  	"case 1"
  	fixup notAFixup ifTrue:
  		[^0].
  
  	"case 2"
  	fixup isNonMergeFixup ifTrue:
  		[deadCode := false. ^0].
  
  	"cases 3 and 4"
  	self assert: fixup isMergeFixup.
  	self traceMerge: fixup.
  	deadCode
  		ifTrue: "case 3"
+ 			["Would like to assert fixup simStackPtr >= methodOrBlockNumTemps
+ 			   but can't because of the initialNils hack."
- 			["Would like to assert fixup simStackPtr >= methodOrBlockNumTemps but can't because
- 			   a) the initialNils hack, b) deadCode removal allows arriving at an isBackwardBranchFixup."
  			 self assert: (fixup simStackPtr >= methodOrBlockNumTemps
+ 						or: [inBlock = InVanillaBlock]).
+ 			 simStackPtr := fixup simStackPtr.
- 						or: [inBlock = InVanillaBlock
- 						or: [fixup isBackwardBranchFixup]]).
- 			 fixup isBackwardBranchFixup ifFalse:
- 				[simStackPtr := fixup simStackPtr].
  			 LowcodeVM ifTrue:
  				[simNativeStackPtr := fixup simNativeStackPtr.
  				simNativeStackSize := fixup simNativeStackSize]]
  		ifFalse: "case 4"
  			[self ssFlushTo: simStackPtr].
  
  	"cases 3 and 4"
  	deadCode := false.
  	fixup isBackwardBranchFixup ifTrue:
  		[fixup simStackPtr: simStackPtr.
  		LowcodeVM ifTrue:
  			[fixup simNativeStackPtr: simNativeStackPtr.
  			 fixup simNativeStackSize: simNativeStackSize]].
  	fixup targetInstruction: self Label.
  	self assert: simStackPtr = fixup simStackPtr.
  	LowcodeVM ifTrue:
  		[self assert: simNativeStackPtr = fixup simNativeStackPtr.
  		 self assert: simNativeStackSize = fixup simNativeStackSize].
  
  	self cCode: '' inSmalltalk:
  		[self assert: fixup simStackPtr = (self debugStackPointerFor: bytecodePC)].
  	self restoreSimStackAtMergePoint: fixup.
  
  	^0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>printRegisterMask: (in category 'debug printing') -----
+ printRegisterMask: registerMask
+ 	<doNotGenerate>
+ 	^String streamContents: [:s| self printRegisterMask: registerMask on: s]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>printSimStack: (in category 'simulation only') -----
+ printSimStack: aSimStackOrFixup
- printSimStack: aSimStack
  	<doNotGenerate>
+ 	(aSimStackOrFixup isKindOf: CogRASSBytecodeFixup)
+ 		ifTrue:
+ 			[self printSimStack: aSimStackOrFixup mergeSimStack toDepth: aSimStackOrFixup simStackPtr spillBase: -1 on: coInterpreter transcript]
+ 		ifFalse:
+ 			[self printSimStack: aSimStackOrFixup toDepth: simStackPtr spillBase: simSpillBase on: coInterpreter transcript]!
- 	self printSimStack: aSimStack toDepth: simStackPtr spillBase: simSpillBase on: coInterpreter transcript!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>restoreSimStackAtMergePoint: (in category 'simulation stack') -----
  restoreSimStackAtMergePoint: fixup
  	<inline: true>
+ 	"All the execution paths reaching a merge point expect everything
+ 	 to be spilled on stack. Throw away all simStack optimization state."
- 	"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."
  	self voidReceiverOptStatus.
  	methodOrBlockNumTemps + 1 to: simStackPtr do:
  		[:i|
  		 (self simStackAt: i)
  			type: SSSpill;
  			offset: FoxMFReceiver - (i - methodOrBlockNumArgs * objectMemory bytesPerOop);
  			register: FPReg;
  			spilled: true].
  	simSpillBase := simStackPtr + 1.
  	LowcodeVM ifTrue:
  		[0 to: simNativeStackPtr do:
  			[ :i |
  			(self simNativeStackAt: i)
  				ensureIsMarkedAsSpilled].
  		simNativeSpillBase := simNativeStackPtr + 1].
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssFlushUpThroughTemporaryVariable: (in category 'simulation stack') -----
  ssFlushUpThroughTemporaryVariable: tempIndex
  	"Any occurrences on the stack of the value being stored (which is the top of stack)
  	 must be flushed, and hence any values colder than them stack."
  	<var: #desc type: #'CogSimStackEntry *'>
+ 	| offset |
  	LowcodeVM ifTrue: [ self ssNativeFlushTo: simNativeStackPtr ].
+ 	offset := (self simStackAt: tempIndex + 1) offset.
+ 	self assert: offset = (self frameOffsetOfTemporary: tempIndex).
  	self ssFlushUpThrough: 
  		[ :desc |
  			desc type = SSBaseOffset
  		 	and: [desc register = FPReg
+ 		 	and: [desc offset = offset ] ] ]!
- 		 	and: [desc offset = (self frameOffsetOfTemporary: tempIndex) ] ] ]!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>traceMerge: (in category 'simulation only') -----
  traceMerge: fixup
  	<cmacro: '(ign) 0'>
+ 	| index |
- 	| index original |
  	(compilationTrace anyMask: 16) ifTrue:
  		[index := (fixups object identityIndexOf: fixup) - 1.
+ 		 coInterpreter transcript
+ 			ensureCr;
+ 			print: index; nextPut: $/; print: index + initialPC;
+ 			nextPut: $:; space.
+ 			fixup printStateOn: coInterpreter transcript.
+ 			coInterpreter transcript cr; flush]!
- 		 (fixup isBackwardBranchFixup and: [compilationPass notNil and: [compilationPass > 1 and: [(original := fixup simStackPtr) < 0]]]) ifTrue:
- 			[fixup simStackPtr: simStackPtr].
- 
- 		 [coInterpreter transcript
- 				ensureCr;
- 				print: index; nextPut: $/; print: index + initialPC;
- 				nextPut: $:; space.
- 				fixup printStateOn: coInterpreter transcript.
- 				coInterpreter transcript cr; flush]
- 			ensure: [original ifNotNil: [fixup simStackPtr: original]]]!



More information about the Vm-dev mailing list