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

commits at source.squeak.org commits at source.squeak.org
Mon Apr 11 17:54:22 UTC 2016


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

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

Name: VMMaker.oscog-cb.1794
Author: cb
Time: 11 April 2016, 10:52:42.79014 am
UUID: 361bc1e7-5399-4bfe-9577-be50efec4d64
Ancestors: VMMaker.oscog-nice.1793

- Full closure activation does not need to fetch the outer context (useless memory read)
- change primitiveSetOrHasIdentityHash to patch the class table if the new hash is set to a behavior (the primitive knows it's a behavior if the second (optional) argument is true)
For example:
FullBlockClosure tryPrimitive: 161 withArgs: {38.true}
- add support for fullClosures in the stack depth finder
- make sure the full closure scheme is fully working in the stack interpreter (there was a problem with copied values)
- fix a bug with registers and full closure in StackToRegisterMappingCogit (register are always pushed on stack for full closure activations)

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

Item was changed:
  ----- Method: CoInterpreter>>activateNewFullClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod."
+ 	| numCopied theMethod methodHeader numTemps |
- 	| numCopied outerContext theMethod methodHeader numTemps |
  	<inline: true>
- 	self break.
- 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	numCopied := self copiedValueCountOfFullClosure: blockClosure.
  	theMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
  	self assert: (objectMemory isOopCompiledMethod: theMethod).
  	methodHeader := self rawHeaderOf: theMethod.
  	(self isCogMethodReference: methodHeader) ifTrue:
  		[^self
  			executeFullCogBlock: (self cogMethodOf: theMethod)
  			closure: blockClosure
  			mayContextSwitch: mayContextSwitch].
  	"How do we know when to compile a block method?
  	 One simple criterion is to check if the block is running within its inner context,
  	 i.e. if the outerContext is married.
  	 Even simpler is to remember the previous block entered via the interpreter and
  	 compile if this is the same one.  But we can thrash trying to compile an uncoggable
  	 method unless we try and remember which ones can't be cogged.  So also record
  	 the last block method we failed to compile and avoid recompiling it."
  	(self methodWithHeaderShouldBeCogged: methodHeader)
  		ifTrue:
  			[theMethod = lastCoggableInterpretedBlockMethod
  				ifTrue:
  					[theMethod ~= lastUncoggableInterpretedBlockMethod ifTrue:
  						[cogit cogFullBlockMethod: theMethod numCopied: numCopied.
  						 (self methodHasCogMethod: theMethod) ifTrue:
  							[^self executeFullCogBlock: (self cogMethodOf: theMethod)
  								closure: blockClosure
  								mayContextSwitch: mayContextSwitch].
  						 cogCompiledCodeCompactionCalledFor ifFalse:
  							[lastUncoggableInterpretedBlockMethod := theMethod]]]
  				ifFalse:
  					[lastCoggableInterpretedBlockMethod := theMethod]]
  		ifFalse:
  			[self maybeFlagMethodAsInterpreted: theMethod].
  
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: objectMemory nilObject. "FxThisContext field"
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: 0. "FoxIFSavedIP"
  	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: FullClosureReceiverIndex ofObject: blockClosure).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + FullClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	methodHeader := objectMemory methodHeaderOf: theMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	numArgs + numCopied + 1 to: numTemps do: [ :i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: theMethod) - 1.
  	
  	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	stackPointer < stackLimit ifTrue:
  		[self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch]!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveSetOrHasIdentityHash (in category 'object access primitives') -----
  primitiveSetOrHasIdentityHash
+ 	| hash oldHash thisReceiver isReceiverAClass |
- 	| hash oldHash thisReceiver |
  	argumentCount = 0 ifTrue:
  		[| hasHash |
  		 hasHash := (objectMemory isNonImmediate: self stackTop)
  						and: [objectMemory hasIdentityHash: self stackTop].
  		 self pop: argumentCount + 1 thenPushBool: hasHash.
  		 ^self].
+ 	argumentCount = 2 
+ 		ifTrue: 
+ 			[isReceiverAClass := self booleanValueOf: self stackTop.
+ 			self successful ifFalse: [self primitiveFailFor: PrimErrBadArgument] ]
+ 		ifFalse: [isReceiverAClass := false].
+ 	hash := self stackIntegerValue: argumentCount - 1.
+ 	thisReceiver := self stackObjectValue: argumentCount.
- 	hash := self stackIntegerValue: 0.
- 	thisReceiver := self stackObjectValue: 1.
  	self successful ifTrue:
  		[oldHash := objectMemory hashBitsOf: thisReceiver.
  		 objectMemory setHashBitsOf: thisReceiver to: hash.
+ 		(isReceiverAClass and: [objectMemory hasSpurMemoryManagerAPI]) ifTrue:
+ 				[objectMemory classAtIndex: hash put: thisReceiver.
+ 				"next line figures out if the index is anbiguous and fix all the instances if needed"
+ 				objectMemory allInstancesOf: thisReceiver].
  		 self pop: argumentCount + 1 thenPushInteger: oldHash]!

Item was added:
+ ----- Method: StackDepthFinder>>pushFullClosure:numCopied: (in category 'instruction decoding') -----
+ pushFullClosure: literal numCopied: numCopied.
+ 	"Push Closure bytecode."
+ 	numCopied = 0
+ 		ifTrue: [self push]
+ 		ifFalse: [numCopied > 1 ifTrue:
+ 					[self drop: numCopied - 1]].!

Item was changed:
  ----- Method: StackInterpreter>>activateNewFullClosureMethod:numArgs:mayContextSwitch: (in category 'control primitives') -----
  activateNewFullClosureMethod: blockClosure numArgs: numArgs mayContextSwitch: mayContextSwitch
  	"Similar to activateNewMethod but for Closure and newMethod."
+ 	| numCopied theMethod methodHeader numTemps |
- 	| numCopied outerContext theMethod methodHeader numTemps |
  	<inline: true>
- 	outerContext := objectMemory fetchPointer: ClosureOuterContextIndex ofObject: blockClosure.
  	numCopied := self copiedValueCountOfFullClosure: blockClosure.
  	theMethod := objectMemory fetchPointer: FullClosureCompiledBlockIndex ofObject: blockClosure.
  	self assert: (objectMemory isOopCompiledMethod: theMethod).
  	self push: instructionPointer.
  	self push: framePointer.
  	framePointer := stackPointer.
  	self push: theMethod.
  	self push: (self encodeFrameFieldHasContext: false isBlock: true numArgs: numArgs).
  	self push: objectMemory nilObject. "FxThisContext field"
  	"Because inst var access is not checked, we must follow the receiver in Spur to ensure it is valid."
  	self push: (objectMemory followField: FullClosureReceiverIndex ofObject: blockClosure).
  
  	"Copy the copied values..."
  	0 to: numCopied - 1 do:
  		[:i|
  		self push: (objectMemory
  					fetchPointer: i + FullClosureFirstCopiedValueIndex
  					ofObject: blockClosure)].
  
  	self assert: (self frameIsBlockActivation: framePointer).
  	self assert: (self frameHasContext: framePointer) not.
  
  	methodHeader := objectMemory methodHeaderOf: theMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  
  	numArgs + numCopied + 1 to: numTemps do: [ :i | self push: objectMemory nilObject].
  
  	instructionPointer := (self initialPCForHeader: methodHeader method: theMethod) - 1.
  	
  	self setMethod: theMethod.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)"
  	stackPointer < stackLimit ifTrue:
  		[self handleStackOverflowOrEventAllowContextSwitch: mayContextSwitch]!

Item was changed:
  ----- Method: StackInterpreter>>fullClosureIn:numArgs:numCopiedValues:compiledBlock: (in category 'control primitives') -----
  fullClosureIn: context numArgs: numArgs numCopiedValues: numCopied compiledBlock: compiledBlock 
  	| newClosure |
  	<inline: true>
  	ClassFullBlockClosureCompactIndex ~= 0
  		ifTrue:
  			[newClosure := objectMemory
  								eeInstantiateSmallClassIndex: ClassFullBlockClosureCompactIndex
  								format: objectMemory indexablePointersFormat
+ 								numSlots: FullClosureFirstCopiedValueIndex + numCopied]
- 								numSlots: ClosureFirstCopiedValueIndex + numCopied]
  		ifFalse:
  			[newClosure := objectMemory
  								eeInstantiateSmallClass: (objectMemory splObj: ClassFullBlockClosure)
  								numSlots: FullClosureFirstCopiedValueIndex + numCopied].
  	"Assume: have just allocated a new closure; it must be young. Thus, can use unchecked stores."
  	objectMemory
  		storePointerUnchecked: ClosureOuterContextIndex ofObject: newClosure withValue: context;
  		storePointerUnchecked: FullClosureCompiledBlockIndex ofObject: newClosure withValue: compiledBlock;
  		storePointerUnchecked: ClosureNumArgsIndex ofObject: newClosure withValue: (objectMemory integerObjectOf: numArgs).
  	^newClosure!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>compileEntireFullBlockMethod: (in category 'compile abstract instructions') -----
- compileEntireFullBlockMethod: numCopied
- 	regArgsHaveBeenPushed := false.
- 	^super compileEntireFullBlockMethod: numCopied!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>compileFullBlockMethodFrameBuild: (in category 'compile abstract instructions') -----
  compileFullBlockMethodFrameBuild: numCopied
  	needsFrame ifFalse:
  		[self initSimStackForFramelessMethod: initialPC.
  		 ^self].
- 	self genPushRegisterArgs.
  	super compileFullBlockMethodFrameBuild: numCopied.
  	self initSimStackForFramefulMethod: initialPC!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>genPrimitiveFullClosureValue (in category 'primitive generators') -----
+ genPrimitiveFullClosureValue
+ 	"Override to push the register args first."
+ 	self break.
+ 	self genPushRegisterArgs.
+ 	^super genPrimitiveFullClosureValue!



More information about the Vm-dev mailing list