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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 21 14:42:31 UTC 2016


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

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

Name: VMMaker.oscog-cb.1828
Author: cb
Time: 21 April 2016, 4:40:41.066653 pm
UUID: 9bde9124-cb83-42bd-a9f4-7e035961afd3
Ancestors: VMMaker.oscog-cb.1827

- Temporarily moved SistaCogit as a subclass of StackToRegisterMappingCogit because I need to compile it every while (sorry about that Eliot... I will try to fix RegisterAllocatingCogit when I can).

- Various fixes to make SistaCogit compile:
--- changed names for method genExt*RemoteTempOrInstVarLongBytecode to avoid C compiler conflict detection.
--- added <inline:true> in extStoreRemoteTempOrInstVarLongBytecode for the interpreter, it's mandatory with gnuification or there is a linking error.
--- change descriptor type to Descriptor instead of AbstractInstruction in sista genJumpIf:, which is a mistake I introduced while removing counter generationg for an: / or: .

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

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genExtStoreAndPopRemoteTempOrInstVarLongBytecode (in category 'bytecode generators') -----
+ genExtStoreAndPopRemoteTempOrInstVarLongBytecode
+ 	^ self genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genExtStorePopRemoteTempOrInstVarLongBytecode (in category 'bytecode generators') -----
- genExtStorePopRemoteTempOrInstVarLongBytecode
- 	^ self genExtStorePopRemoteTempOrInstVarLongBytecode: true!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>genExtStorePopRemoteTempOrInstVarLongBytecode: (in category 'bytecode generators') -----
- genExtStorePopRemoteTempOrInstVarLongBytecode: popBoolean
- 	| index |
- 	extB := 0. "simple cogit don't use the extra flag"
- 	(byte2 noMask: 1 << 7)
- 		ifTrue: 
- 			[ self genStorePop: popBoolean RemoteTemp: byte1 At: byte2.
- 			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
- 		ifFalse: 
- 			[ index := byte1 + (extA << 8).
- 			extA := 0.
- 			(coInterpreter isWriteMediatedContextInstVarIndex: index)
- 				ifTrue: [ self 
- 						genStorePop: popBoolean 
- 						MaybeContextRemoteInstVar: index 
- 						ofObjectAt: byte2 - (1 << 7) ]
- 				ifFalse: [ self 
- 						genStorePop: popBoolean 
- 						RemoteInstVar: index 
- 						ofObjectAt: byte2 - (1 << 7)  ] ].
- 	^ 0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: (in category 'bytecode generators') -----
+ genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: popBoolean
+ 	| index |
+ 	extB := 0. "simple cogit don't use the extra flag"
+ 	(byte2 noMask: 1 << 7)
+ 		ifTrue: 
+ 			[ self genStorePop: popBoolean RemoteTemp: byte1 At: byte2.
+ 			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
+ 		ifFalse: 
+ 			[ index := byte1 + (extA << 8).
+ 			extA := 0.
+ 			(coInterpreter isWriteMediatedContextInstVarIndex: index)
+ 				ifTrue: [ self 
+ 						genStorePop: popBoolean 
+ 						MaybeContextRemoteInstVar: index 
+ 						ofObjectAt: byte2 - (1 << 7) ]
+ 				ifFalse: [ self 
+ 						genStorePop: popBoolean 
+ 						RemoteInstVar: index 
+ 						ofObjectAt: byte2 - (1 << 7)  ] ].
+ 	^ 0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtStoreRemoteTempOrInstVarLongBytecode (in category 'bytecode generators') -----
  genExtStoreRemoteTempOrInstVarLongBytecode
+ 	^ self genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: false!
- 	^ self genExtStorePopRemoteTempOrInstVarLongBytecode: false!

Item was changed:
+ StackToRegisterMappingCogit subclass: #SistaCogit
- RegisterAllocatingCogit subclass: #SistaCogit
  	instanceVariableNames: 'numCounters counters counterIndex initialCounterValue ceTrapTrampoline branchReachedOnlyForCounterTrip'
  	classVariableNames: 'CounterBytes MaxCounterValue'
  	poolDictionaries: 'VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!
  
  !SistaCogit commentStamp: 'eem 4/19/2016 14:22' prior: 0!
  A SistaCogit is a refinement of RegisterAllocatingCogit that generates code suitable for dynamic optimization by Sista, the Speculative Inlining Smalltalk Architecture, a project by Clément Bera and Eliot Miranda.  Sista is an optimizer that exists in the Smalltalk image, /not/ in the VM,  and optimizes by substituting normal bytecoded methods by optimized bytecoded methods that may use special bytecodes for which the Cogit can generate faster code.  These bytecodes eliminate overheads such as bounds checks or polymorphic code (indexing Array, ByteArray, String etc).  But the bulk of the optimization performed is in inlining blocks and sends for the common path.
  
  The basic scheme is that SistaCogit generates code containing performance counters.  When these counters trip, a callback into the image is performed, at which point Sista analyses some portion of the stack, looking at performance data for the methods on the stack, and optimises based on the stack and performance data.  Execution then resumes in the optimized code.
  
  SistaCogit adds counters to conditional branches.  Each branch has an executed and a taken count, implemented at the two 16-bit halves of a single 32-bit word.  Each counter pair is initialized with initialCounterValue.  On entry to the branch the executed count is decremented and if the count goes below zero the ceMustBeBooleanAdd[True|False] trampoline called.  The trampoline distinguishes between true mustBeBoolean and counter trips because in the former the register temporarily holding the counter value will contain zero.  Then the condition is tested, and if the branch is taken the taken count is decremented.  The two counter values allow an optimizer to collect basic block execution paths and to know what are the "hot" paths through execution that are worth agressively optimizing.  Since conditional branches are about 1/6 as frequent as sends, and since they can be used to determine the hot path through code, they are a better choice to count than, for example, method or block entry.
  
  SistaCogit implements picDataFor:into: that fills an Array with the state of the counters in a method and the state of each linked send in a method.  This is used to implement a primitive used by the optimizer to answer the branch and send data for a method as an Array.
  
  Instance Variables
  	counterIndex:			<Integer>
  	counterMethodCache:	<CogMethod>
  	counters:				<Array of AbstractInstruction>
  	initialCounterValue:		<Integer>
  	numCounters:			<Integer>
  	picData:				<Integer Oop>
  	picDataIndex:			<Integer>
  	prevMapAbsPCMcpc:	<Integer>
  
  counterIndex
  	- xxxxx
  
  counterMethodCache
  	- xxxxx
  
  counters
  	- xxxxx
  
  initialCounterValue
  	- xxxxx
  
  numCounters
  	- xxxxx
  
  picData
  	- xxxxx
  
  picDataIndex
  	- xxxxx
  
  prevMapAbsPCMcpc
  	- xxxxx
  !

Item was changed:
  ----- Method: SistaCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	"The heart of performance counting in Sista.  Conditional branches are 6 times less
  	 frequent than sends and can provide basic block frequencies (send counters can't).
  	 Each conditional has a 32-bit counter split into an upper 16 bits counting executions
  	 and a lower half counting untaken executions of the branch.  Executing the branch
  	 decrements the upper half, tripping if the count goes negative.  Not taking the branch
  	 decrements the lower half.  N.B. We *do not* eliminate dead branches (true ifTrue:/true ifFalse:)
  	 so that scanning for send and branch data is simplified and that branch data is correct."
  	<inline: false>
  	| ok counterAddress countTripped retry nextPC nextDescriptor |
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #countTripped type: #'AbstractInstruction *'>
+ 	<var: #nextDescriptor type: #'BytecodeDescriptor *'>
- 	<var: #nextDescriptor type: #'AbstractInstruction *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
  	
  	branchReachedOnlyForCounterTrip ifTrue: 
  		[ branchReachedOnlyForCounterTrip := false.
  		^ self genCounterTripOnlyJumpIf: boolean to: targetBytecodePC ].
  	
  	boolean == objectMemory falseObject ifTrue:
  		[ "detection of and: / or:"
  		nextPC := bytecodePC + (self generatorAt: byte0) numBytes.
  		nextDescriptor := self generatorAt: (objectMemory fetchByte: nextPC ofObject: methodObj) + bytecodeSetOffset.
  		nextDescriptor generator ==  #genPushConstantTrueBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].
  		nextDescriptor := self generatorAt: (objectMemory fetchByte: targetBytecodePC ofObject: methodObj) + bytecodeSetOffset.
  		nextDescriptor generator ==  #genPushConstantFalseBytecode ifTrue: [ ^ super genJumpIf: boolean to: targetBytecodePC ].  ].
  
  	extA := 0.
  
  	self ssFlushTo: simStackPtr - 1.
  	self ssTop popToReg: TempReg.
  	self ssPop: 1.
  
  	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
  	self ssAllocateRequiredReg: SendNumArgsReg.
  
  	retry := self Label.
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: SendNumArgsReg.
  	counterIndex := counterIndex + 1.
  
  	"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 genFallsThroughCountLogicCounterReg: SendNumArgsReg counterAddress: counterAddress.
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."
  	
  	countTripped jmpTarget:
  		(self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline])).
  						
  	"If we're in an image which hasn't got the Sista code loaded then the ceCounterTripped:
  	 trampoline will return directly to machine code, returning the boolean.  So the code should
  	 jump back to the retry point. The trampoline makes sure that TempReg has been reloaded."
  	self annotateBytecode: self Label.
  
  	self Jump: retry.
  	
  	ok jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SistaCogit>>scanMethod (in category 'compile abstract instructions') -----
  scanMethod
  	"Scan the method (and all embedded blocks) to determine
  		- what the last bytecode is; extra bytes at the end of a method are used to encode things like source pointers or temp names
  		- if the method needs a frame or not
  		- what are the targets of any backward branches.
  		- how many blocks it creates
  		- how many counters it needs/conditional branches it contains
  	 Answer the block count or on error a negative error code"
+ 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta numFixups |
- 	| latestContinuation nExts descriptor pc numBlocks distance targetPC framelessStackDelta |
  	<var: #descriptor type: #'BytecodeDescriptor *'>
+ 	self flag: 'numFixup should be reverted to inst var when moving back sistaCogit as subclass of RegisterAllocatingCogit'.
  	needsFrame := false.
  	numFixups := 0.
  	prevBCDescriptor := nil.
  	numCounters := 0.
  	NewspeakVM ifTrue:
  		[numIRCs := 0].
  	(primitiveIndex > 0
  	 and: [coInterpreter isQuickPrimitiveIndex: primitiveIndex]) ifTrue:
  		[^0].
  	pc := latestContinuation := initialPC.
  	numBlocks := framelessStackDelta := nExts := extA := extB := 0.
  	[pc <= endPC] whileTrue:
  		[byte0 := (objectMemory fetchByte: pc ofObject: methodObj) + bytecodeSetOffset.
  		 descriptor := self generatorAt: byte0.
  		 descriptor isExtension ifTrue:
  			[descriptor opcode = Nop ifTrue: "unknown bytecode tag; see Cogit class>>#generatorTableFrom:"
  				[^EncounteredUnknownBytecode].
  			 self loadSubsequentBytesForDescriptor: descriptor at: pc.
  			 self perform: descriptor generator].
  		 (descriptor isReturn
  		  and: [pc >= latestContinuation]) ifTrue:
  			[endPC := pc].
  		 needsFrame ifFalse:
  			[(descriptor needsFrameFunction isNil
  			  or: [self perform: descriptor needsFrameFunction with: framelessStackDelta])
  				ifTrue: [needsFrame := true]
  				ifFalse: [framelessStackDelta := framelessStackDelta + descriptor stackDelta]].
  		 descriptor isBranch ifTrue:
  			[distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 (self isBackwardBranch: descriptor at: pc exts: nExts in: methodObj)
  				ifTrue: [self initializeFixupAt: targetPC - initialPC]
  				ifFalse:
  					[latestContinuation := latestContinuation max: targetPC.
  					numFixups := numFixups + 1.
  					 (descriptor isBranchTrue or: [descriptor isBranchFalse]) ifTrue:
  						[numCounters := numCounters + 1]]].
  		 descriptor isBlockCreation ifTrue:
  			[numBlocks := numBlocks + 1.
  			 distance := self spanFor: descriptor at: pc exts: nExts in: methodObj.
  			 targetPC := pc + descriptor numBytes + distance.
  			 latestContinuation := latestContinuation max: targetPC.
  			 numFixups := numFixups + 1].
  		 NewspeakVM ifTrue:
  			[descriptor hasIRC ifTrue:
  				[numIRCs := numIRCs + 1]].
  		 pc := pc + descriptor numBytes.
  		 descriptor isExtension
  			ifTrue: [nExts := nExts + 1]
  			ifFalse: [nExts := extA := extB := 0].
  		 prevBCDescriptor := descriptor].
  	^numBlocks!

Item was changed:
  ----- Method: StackInterpreter>>extStoreRemoteTempOrInstVarLongBytecode (in category 'stack bytecodes') -----
  extStoreRemoteTempOrInstVarLongBytecode
+ 	<inline: true>
  	| slotIndex tempIndex object |
  	slotIndex := self fetchByte.
  	tempIndex := self fetchByte.
  	self fetchNextBytecode.
  	(tempIndex noMask: self remoteIsInstVarAccess)
  		ifTrue: [self storeRemoteTemp: slotIndex inVectorAt: tempIndex]
  		ifFalse: 
  			[ slotIndex := slotIndex + (extA << 8).
  			extA := extB := 0.
  			object := self temporary: tempIndex in: localFP.
  			self storeMaybeContext: object receiverVariable: slotIndex withValue: self internalStackTop ]!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>genExtStorePopRemoteTempOrInstVarLongBytecode: (in category 'bytecode generators') -----
- genExtStorePopRemoteTempOrInstVarLongBytecode: boolean
- 	| index maybeContext needsStoreCheck |
- 	needsStoreCheck := self sistaNeedsStoreCheck.
- 	maybeContext := self extBSpecifiesMaybeContext.
- 	extB := 0.
- 	(byte2 noMask: coInterpreter remoteIsInstVarAccess)
- 		ifTrue: 
- 			[ self genStorePop: boolean RemoteTemp: byte1 At: byte2 needsStoreCheck: needsStoreCheck.
- 			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
- 		ifFalse: 
- 			[ index := byte1 + (extA << 8).
- 			extA := 0.
- 			((coInterpreter isWriteMediatedContextInstVarIndex: index) and: [ maybeContext ])
- 				ifTrue: [ self 
- 						genStorePop: boolean 
- 						MaybeContextRemoteInstVar: index 
- 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
- 						needsStoreCheck: needsStoreCheck ]
- 				ifFalse: [ self 
- 						genStorePop: boolean 
- 						RemoteInstVar: index 
- 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
- 						needsStoreCheck: needsStoreCheck ] ].
- 	^ 0!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: (in category 'bytecode generators') -----
+ genExtStorePopRemoteTempOrInstVarLongBytecodePopBoolean: boolean
+ 	| index maybeContext needsStoreCheck |
+ 	needsStoreCheck := self sistaNeedsStoreCheck.
+ 	maybeContext := self extBSpecifiesMaybeContext.
+ 	extB := 0.
+ 	(byte2 noMask: coInterpreter remoteIsInstVarAccess)
+ 		ifTrue: 
+ 			[ self genStorePop: boolean RemoteTemp: byte1 At: byte2 needsStoreCheck: needsStoreCheck.
+ 			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
+ 		ifFalse: 
+ 			[ index := byte1 + (extA << 8).
+ 			extA := 0.
+ 			((coInterpreter isWriteMediatedContextInstVarIndex: index) and: [ maybeContext ])
+ 				ifTrue: [ self 
+ 						genStorePop: boolean 
+ 						MaybeContextRemoteInstVar: index 
+ 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
+ 						needsStoreCheck: needsStoreCheck ]
+ 				ifFalse: [ self 
+ 						genStorePop: boolean 
+ 						RemoteInstVar: index 
+ 						ofObjectAt: byte2 - coInterpreter remoteIsInstVarAccess 
+ 						needsStoreCheck: needsStoreCheck ] ].
+ 	^ 0!



More information about the Vm-dev mailing list