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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 4 23:18:30 UTC 2015


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

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

Name: VMMaker.oscog-eem.1039
Author: eem
Time: 4 February 2015, 3:17:04.327 pm
UUID: 931d69b1-7be3-42dd-8833-1ba325d2b5f2
Ancestors: VMMaker.oscog-eem.1038

Allow primitivePerformWithArgs to avoid fetchClassOf:
in Spur by making the last arg to
primitiveObject:perform:withArguments:lookedUpIn:
lookupClassOrNil.

Update Slang constan folding to include nil isNil/notNil.

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

Item was changed:
  ----- Method: CCodeGenerator>>isConstantNode:valueInto: (in category 'utilities') -----
  isConstantNode: aNode valueInto: aBlock
  	"Answer if aNode evaluates to a constant, and if so, evaluate aBlock with the value of that constant."
  
  	aNode isConstant ifTrue:
  		[aBlock value: aNode value.
  		 ^true].
+ 	(aNode isVariable
+ 	 and: [aNode name = #nil]) ifTrue:
+ 		[aBlock value: nil.
+ 		 ^true].
  	aNode isSend ifFalse:
  		[^false].
  	(self anyMethodNamed: aNode selector)
  		ifNil:
  			[(VMBasicConstants valueOfBasicSelector: aNode selector) ifNotNil:
  				[:value|
  				 aBlock value: value.
  				 ^true]]
  		ifNotNil:
  			[:m|
  			(m statements size = 1
  			 and: [m statements last isReturn]) ifTrue:
  				[^self isConstantNode: m statements last expression valueInto: aBlock]].
  	^false!

Item was changed:
  ----- Method: CCodeGenerator>>nilOrBooleanConstantReceiverOf: (in category 'utilities') -----
  nilOrBooleanConstantReceiverOf: aNode
  	"Answer nil or the boolean constant that is the receiver of the given message send.
  	 Used to suppress conditional code when the condition is a translation-time constant."
  
  	| val receiver argument |
  	generateDeadCode ifTrue:[^nil].
  	((self isConstantNode: aNode valueInto: [:v| val := v])
  	 and: [#(true false) includes: val]) ifTrue:
  		[^val].
  	aNode isSend ifTrue:
  		[aNode selector == #not ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:bool| ^bool not]].
+ 		 ((#(isNil notNil) includes: aNode selector)
+ 		  and: [self isNilConstantReceiverOf: aNode]) ifTrue:
+ 			[^aNode selector == #isNil].
  		 ((#(or: and:) includes: aNode selector)
  		 and: [aNode args last isStmtList
  		 and: [aNode args last statements size = 1]]) ifTrue:
  			[(self nilOrBooleanConstantReceiverOf: aNode receiver) ifNotNil:
  				[:rcvr|
  				((rcvr == false and: [aNode selector == #and:])
  				 or: [rcvr == true and: [aNode selector == #or:]]) ifTrue:
  					[^rcvr].
  				(self nilOrBooleanConstantReceiverOf: aNode args last statements first) ifNotNil:
  					[:arg|
  					^rcvr perform: aNode selector with: [arg]]]].
  		 ((#(= ~= < > <= >=) includes: aNode selector)
  		  and: [(self isConstantNode: aNode receiver valueInto: [:v| receiver := v])
  		  and: [receiver isInteger
  		  and: [(self isConstantNode: aNode args first valueInto: [:v| argument := v])
  		  and: [argument isInteger]]]]) ifTrue:
  			[^receiver perform: aNode selector with: argument]].
  	^nil!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitivePerformWithArgs (in category 'control primitives') -----
  primitivePerformWithArgs
+ 	self primitiveObject: (self stackValue: 2)
- 
- 	| lookupClass rcvr |
- 	rcvr := self stackValue: 2.
- 	lookupClass := objectMemory fetchClassOf: rcvr.
- 
- 	self primitiveObject: rcvr "a.k.a. self stackValue: 2"
  		perform: (self stackValue: 1)
  		withArguments: self stackTop
+ 		lookedUpIn: nil!
- 		lookedUpIn: lookupClass!

Item was changed:
  ----- Method: StackInterpreter>>primitiveObject:perform:withArguments:lookedUpIn: (in category 'control primitives') -----
+ primitiveObject: actualReceiver perform: selector withArguments: argumentArray lookedUpIn: lookupClassOrNil
- primitiveObject: actualReceiver perform: selector withArguments: argumentArray lookedUpIn: lookupClass
  	"Common routine used by perform:withArgs:, perform:withArgs:inSuperclass:,
  	 object:perform:withArgs:inClass: et al.  Answer nil on success.
  
  	 NOTE:  The case of doesNotUnderstand: is not a failure to perform.
  	 The only failures are arg types and consistency of argumentCount.
  
  	 Since we're in the stack VM we can assume there is space to push the arguments
  	 provided they are within limits (max argument count is 15).  We can therefore deal
  	 with the arbitrary amount of state to remove from the stack (lookup class, selector,
  	 mirror receiver) and arbitrary argument orders by deferring popping anything until
  	 we know whether the send has succeeded.  So on failure we merely have to remove
  	 the actual receiver and arguments pushed, and on success we have to slide the actual
  	 receiver and arguments down to replace the original ones."
+ 	<inline: true>
- 
  	| arraySize performArgCount delta |
  	(objectMemory isArray: argumentArray) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
  	"Check if number of arguments is reasonable; MaxNumArgs isn't available
  	 so just use LargeContextSize"
  	arraySize := objectMemory numSlotsOf: argumentArray.
  	arraySize > LargeContextSlots ifTrue:
  		[^self primitiveFailFor: PrimErrBadNumArgs].
  
  	performArgCount := argumentCount.
  	"Push newMethod to save it in case of failure,
  	 then push the actual receiver and args out of the array."
  	self push: newMethod.
  	self push: actualReceiver.
  	"Copy the arguments to the stack, and execute"
  	1 to: arraySize do:
  		[:index| self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray)].
  	argumentCount := arraySize.
  	messageSelector := selector.
  	self sendBreakpoint: messageSelector receiver: actualReceiver.
  	self printSends ifTrue:
+ 		[self printActivationNameForSelector: messageSelector
+ 				startClass: (lookupClassOrNil isNil
+ 								ifTrue: [objectMemory classForClassTag: lkupClassTag]
+ 								ifFalse: [lookupClassOrNil]);
+ 			cr].
+ 	self findNewMethodInClassTag: (lookupClassOrNil isNil
+ 										ifTrue: [objectMemory fetchClassTagOf: actualReceiver]
+ 										ifFalse: [objectMemory classTagForClass: lookupClassOrNil]).
- 		[self printActivationNameForSelector: messageSelector startClass: lookupClass; cr].
- 	self findNewMethodInClassTag: (objectMemory classTagForClass: lookupClass).
  
  	"Only test CompiledMethods for argument count - any other objects playacting as CMs will have to take their chances"
  	((objectMemory isOopCompiledMethod: newMethod)
  	  and: [(self argumentCountOf: newMethod) ~= argumentCount]) ifTrue:
  		["Restore the state by popping all those array entries and pushing back the selector and array, and fail"
  		 self pop: arraySize + 1.
  		 newMethod := self popStack.
  		 ^self primitiveFailFor: PrimErrBadNumArgs].
  
  	"Cannot fail this primitive from here-on.  Slide the actual receiver and arguments down
  	 to replace the perform arguments and saved newMethod and then execute the new
  	 method. Use argumentCount not arraySize because an MNU may have changed it."
  	delta := objectMemory wordSize * (performArgCount + 2). "+2 = receiver + saved newMethod"
  	argumentCount * objectMemory wordSize to: 0 by: objectMemory wordSize negated do:
  		[:offset|
  		stackPages
  			longAt: stackPointer + offset + delta
  			put: (stackPages longAt: stackPointer + offset)].
  	self pop: performArgCount + 2.
  	self executeNewMethod.
  	self initPrimCall.  "Recursive xeq affects primErrorCode"
  	^nil!



More information about the Vm-dev mailing list