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

commits at source.squeak.org commits at source.squeak.org
Tue Sep 17 20:40:25 UTC 2013


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

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

Name: VMMaker.oscog-eem.385
Author: eem
Time: 17 September 2013, 1:37:16.964 pm
UUID: b410257e-4d71-461d-b00a-e244c049477c
Ancestors: VMMaker.oscog-eem.384

Streamline the sendBreak:point:receiver: monstrosity and make it
accept immediate selectors.

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

Item was changed:
  ----- Method: CoInterpreter>>ceDynamicSuperSend:to:numArgs: (in category 'trampolines') -----
  ceDynamicSuperSend: selector to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked dynamic super send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	<option: #NewspeakVM>
  	| class classTag canLinkCacheTag errSelIdx cogMethod mClassMixin mixinApplication |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: ((objectMemory isIntegerObject: rcvr) or: [objectMemory addressCouldBeObj: rcvr]).
+ 	self sendBreakpoint: selector receiver: rcvr.
- 	self sendBreak: selector + BaseHeaderSize
- 		point: (objectMemory lengthOf: selector)
- 		receiver: rcvr.
  	mClassMixin := self mMethodClass.
  	mixinApplication := self 
  							findApplicationOfTargetMixin: mClassMixin
  							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
  	self assert: (objectMemory lengthOf: mixinApplication) > (InstanceSpecificationIndex + 1).
  	classTag := self classTagForClass: (self superclassOf: mixinApplication).
  	class := objectMemory fetchClassOf: rcvr. "what about the read barrier??"
  	canLinkCacheTag := (objectMemory isYoungObject: class) not or: [cogit canLinkToYoungClasses].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the correct
  				  selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 (cogMethod selector = selector
  		 and: [canLinkCacheTag]) ifTrue:
  			[cogit
  				linkSendAt: (stackPages longAt: stackPointer)
  				in: (self mframeHomeMethod: framePointer)
  				to: cogMethod
  				offset: cogit dynSuperEntryOffset
  				receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSend:super:to:numArgs: (in category 'trampolines') -----
  ceSend: selector super: superNormalBar to: rcvr numArgs: numArgs
  	"Entry-point for an unlinked send in a CogMethod.  Smalltalk stack looks like
  					receiver
  					args
  		head sp ->	sender return pc
  		
  	If an MNU then defer to handleMNUInMachineCodeTo:... which will dispatch the MNU and
  	may choose to allocate a closed PIC with a fast MNU dispatch for this send.  Otherwise
  	attempt to link the send site as efficiently as possible.  All link attempts may fail; e.g.
  	because we're out of code memory.
  
  	Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	depending on whether the target method is cogged or not."
  	<api>
  	| classTag canLinkCacheTag errSelIdx cogMethod |
  	<inline: false>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #newCogMethod type: #'CogMethod *'>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: ((objectMemory isIntegerObject: rcvr) or: [objectMemory addressCouldBeObj: rcvr]).
+ 	self sendBreakpoint: selector receiver: rcvr.
- 	self sendBreak: selector + BaseHeaderSize
- 		point: (objectMemory lengthOf: selector)
- 		receiver: rcvr.
  	superNormalBar = 0
  		ifTrue: [classTag := objectMemory fetchClassTagOf: rcvr]
  		ifFalse: [classTag := objectMemory classTagForClass: (self superclassOf: (self methodClassOf: (self frameMethodObject: framePointer)))].
  	canLinkCacheTag := objectMemory hasSpurMemoryManagerAPI
  						or: [(objectMemory isYoungObject: classTag) not or: [cogit canLinkToYoungClasses]].
  	argumentCount := numArgs.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[(canLinkCacheTag
  				  and: [errSelIdx = SelectorDoesNotUnderstand
  				  and: [(cogMethod := cogit cogMNUPICSelector: messageSelector
  											methodOperand: (self mnuMethodOrNilFor: rcvr)
  											numArgs: argumentCount) asUnsignedInteger
  						> cogit minCogMethodAddress]]) ifTrue:
  						[cogit
  							linkSendAt: (stackPages longAt: stackPointer)
  							in: (self mframeHomeMethod: framePointer)
  							to: cogMethod
  							offset: (superNormalBar = 0
  									ifTrue: [cogit entryOffset]
  									ifFalse: [cogit noCheckEntryOffset])
  							receiver: rcvr].
  				self handleMNU: errSelIdx
  					InMachineCodeTo: rcvr
  					classForMessage: (objectMemory classForClassTag: classTag).
  				self assert: false "NOTREACHED"]].
  	"Method found and has a cog method.  Attempt to link to it.  The receiver's class may be young.
  	 If the Cogit can't store young classes in inline caches we can link to an open PIC instead."
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[cogMethod := self cogMethodOf: newMethod.
  		 cogMethod selector = objectMemory nilObject
  			ifTrue: [cogit setSelectorOf: cogMethod to: selector]
  			ifFalse:
  				["Deal with anonymous accessors, e.g. in Newspeak.  The cogMethod may not have the
  				  correct selector.  If not, try and compile a new method with the correct selector."
  				 cogMethod selector ~= selector ifTrue:
  					[(cogit cog: newMethod selector: selector) ifNotNil:
  						[:newCogMethod| cogMethod := newCogMethod]]].
  		 (cogMethod selector = selector
  		  and: [canLinkCacheTag])
  			ifTrue:
  				[cogit
  					linkSendAt: (stackPages longAt: stackPointer)
  					in: (self mframeHomeMethod: framePointer)
  					to: cogMethod
  					offset: (superNormalBar = 0
  								ifTrue: [cogit entryOffset]
  								ifFalse: [cogit noCheckEntryOffset])
  					receiver: rcvr]
  			ifFalse: "If patchToOpenPICFor:.. returns we're out of code memory"
  				[cogit
  					patchToOpenPICFor: selector
  					numArgs: numArgs
  					receiver: rcvr].
  		 instructionPointer := self popStack.
  		 self executeNewMethod.
  		 self assert: false "NOTREACHED"].
  	instructionPointer := self popStack.
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceSendAbort:to:numArgs: (in category 'trampolines') -----
  ceSendAbort: selector to: rcvr numArgs: numArgs
  	"Entry-point for an abort send in a CogMethod (aboutToReturn:through:, cannotReturn: et al).
  	 Try and dispatch the send, but the send may turn into an MNU in which case defer to
  	 handleMNUInMachineCodeTo:... which will dispatch the MNU.
  
  	 Continue execution via either executeMethod or interpretMethodFromMachineCode:
  	 depending on whether the target method is cogged or not."
  	<api>
  	| classTag errSelIdx |
  	<inline: false>
  	"self printExternalHeadFrame"
  	"self printStringOf: selector"
  	cogit assertCStackWellAligned.
  	self assert: ((objectMemory isIntegerObject: rcvr) or: [objectMemory addressCouldBeObj: rcvr]).
+ 	self sendBreakpoint: selector receiver: rcvr.
- 	self sendBreak: selector + BaseHeaderSize
- 		point: (objectMemory lengthOf: selector)
- 		receiver: rcvr.
  	argumentCount := numArgs.
  	classTag := objectMemory fetchClassTagOf: rcvr.
  	(self lookupInMethodCacheSel: selector classTag: classTag)
  		ifTrue:"check for coggability because method is in the cache"
  			[self
  				ifAppropriateCompileToNativeCode: newMethod
  				selector: selector]
  		ifFalse:
  			[messageSelector := selector.
  			 (errSelIdx := self lookupMethodNoMNUEtcInClass: (objectMemory classForClassTag: classTag)) ~= 0 ifTrue:
  				[self handleMNU: errSelIdx InMachineCodeTo: rcvr classForMessage: (objectMemory classForClassTag: classTag).
  				"NOTREACHED"
  				self assert: false]].
  	instructionPointer := self popStack.
  	(self maybeMethodHasCogMethod: newMethod) ifTrue:
  		[self executeNewMethod.
  		 self assert: false
  		 "NOTREACHED"].
  	^self interpretMethodFromMachineCode
  	"NOTREACHED"!

Item was changed:
  ----- Method: CoInterpreter>>ceTraceLinkedSend: (in category 'debug support') -----
  ceTraceLinkedSend: theReceiver
  	| cogMethod |
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	cogMethod := self cCoerceSimple: (self stackTop - cogit traceLinkedSendOffset)
  						to: #'CogMethod *'.
  	"cogit recordSendTrace ifTrue: is implicit; wouldn't compile the call otherwise."
  	self recordTrace: (objectMemory fetchClassOf: theReceiver)
  		thing: cogMethod selector
  		source: TraceIsFromMachineCode.
  	cogit printOnTrace ifTrue:
  		[self printActivationNameFor: cogMethod methodObject
  			receiver: theReceiver
  			isBlock: false
  			firstTemporary: nil;
  			cr].
+ 	self sendBreakpoint: cogMethod selector receiver: theReceiver!
- 	self sendBreak: cogMethod selector + BaseHeaderSize
- 		point: (objectMemory lengthOf: cogMethod selector)
- 		receiver: theReceiver!

Item was changed:
  ----- Method: CoInterpreter>>commonSend (in category 'message sending') -----
  commonSend
  	"Send a message, starting lookup with the receiver's class."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeNamed: 'commonSend' inCase: #singleExtendedSendBytecode>
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (objectMemory lengthOf: messageSelector)
- 		receiver: (self internalStackValue: argumentCount).
  	cogit recordSendTrace ifTrue:
  		[self recordTrace: lkupClass thing: messageSelector source: TraceIsFromInterpreter.
  		cogit printOnTrace ifTrue:
  			[self printActivationNameForSelector: messageSelector startClass: lkupClass; cr]].
  	self internalFindNewMethod.
  	self internalExecuteNewMethod.
  	self fetchNextBytecode!

Item was changed:
  ----- Method: CoInterpreter>>implicitReceiverFor:mixin:implementing: (in category 'newspeak bytecode support') -----
  implicitReceiverFor: rcvr mixin: mixin implementing: selector
  	"This is used to implement the innards of the pushImplicitReceiverBytecode,
  	 used for implicit receiver sends in NS2/NS3.  Find the nearest lexically-enclosing
  	 implementation of selector by searching up the static chain of anObject,
  	 starting at mixin's application.  This is an iterative implementation derived from
  
  	<ContextPart> implicitReceiverFor: obj <Object>
  					withMixin: mixin <Mixin>
  					implementing: selector <Symbol> ^<Object>"
  
  	<api>
  	<option: #NewspeakVM>
  	cogit breakOnImplicitReceiver ifTrue:
+ 		[self sendBreakpoint: selector receiver: nil].
- 		[self sendBreak: selector + BaseHeaderSize
- 			point: (objectMemory lengthOf: selector)
- 			receiver: nil].
  	^super implicitReceiverFor: rcvr mixin: mixin implementing: selector!

Item was changed:
  ----- Method: CogVMSimulator>>primitivePerform (in category 'debugging traps') -----
  primitivePerform
  	| selector |
  	selector := self stackValue: argumentCount - 1.
+ 	self sendBreakpoint: selector receiver: (self stackValue: argumentCount).
- 	self sendBreak: selector + BaseHeaderSize
- 		point: (objectMemory lengthOf: selector)
- 		receiver: (self stackValue: argumentCount).
  	(self filterPerformOf: selector to: (self stackValue: argumentCount)) ifTrue:
  		[^self pop: argumentCount].
  	^super primitivePerform!

Item was changed:
  ----- Method: NewspeakInterpreter>>commonSend (in category 'message sending') -----
  commonSend
  	"Send a message, starting lookup with the receiver's class."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeNamed: 'commonSend' inCase: #singleExtendedSendBytecode>
  	self fastLogSend: messageSelector.
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (self lengthOf: messageSelector)
- 		receiver: (self internalStackValue: argumentCount).
  	self internalFindNewMethod.
  	self internalExecuteNewMethod.
  	self fetchNextBytecode!

Item was changed:
  ----- Method: NewspeakInterpreter>>lookupMethodInClass: (in category 'message sending') -----
  lookupMethodInClass: class
  	| currentClass dictionary found rclass |
  	<inline: false>
  
  	currentClass := class.
  	[currentClass ~= nilObj]
  		whileTrue:
  		[dictionary := self fetchPointer: MessageDictionaryIndex ofObject: currentClass.
  		dictionary = nilObj ifTrue:
  			["MethodDict pointer is nil (hopefully due a swapped out stub)
  				-- raise exception #cannotInterpret:."
  			self pushRemappableOop: currentClass.  "may cause GC!!"
  			self createActualMessageTo: class.
  			currentClass := self popRemappableOop.
  			messageSelector := self splObj: SelectorCannotInterpret.
  			self fastLogSend: messageSelector.
+ 			self sendBreakpoint: messageSelector receiver: nil.
- 			self sendBreak: messageSelector + BaseHeaderSize
- 				point: (self lengthOf: messageSelector)
- 				receiver: nil.
  			^ self lookupMethodInClass: (self superclassOf: currentClass)].
  		found := self lookupMethodInDictionary: dictionary.
  		found ifTrue: [^currentClass].
  		currentClass := self superclassOf: currentClass].
  
  	"Could not find #doesNotUnderstand: -- unrecoverable error."
  	messageSelector = (self splObj: SelectorDoesNotUnderstand) ifTrue:
  		[self error: 'Recursive not understood error encountered'].
  
  	"Cound not find a normal message -- raise exception #doesNotUnderstand:"
  	self pushRemappableOop: class.  "may cause GC!!"
  	self createActualMessageTo: class.
  	rclass := self popRemappableOop.
  	messageSelector := self splObj: SelectorDoesNotUnderstand.
  	RecordSendTrace ifTrue:
  		[self fastLogSend: messageSelector].
  	self sendBreak: messageSelector + BaseHeaderSize
  		point: (self lengthOf: messageSelector)
  		receiver: nil.
  	^ self lookupMethodInClass: rclass!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitivePerform (in category 'control primitives') -----
  primitivePerform
  	| performSelector newReceiver selectorIndex lookupClass performMethod |
  	performSelector := messageSelector.
  	performMethod := newMethod.
  	messageSelector := self stackValue: argumentCount - 1.
  	newReceiver := self stackValue: argumentCount.
  
  	"NOTE: the following lookup may fail and be converted to #doesNotUnderstand:, so we must adjust argumentCount and slide args now, so that would work."
  
  	"Slide arguments down over selector"
  	argumentCount := argumentCount - 1.
  	selectorIndex := self stackPointerIndex - argumentCount.
  	self
  		transfer: argumentCount
  		fromIndex: selectorIndex + 1
  		ofObject: activeContext
  		toIndex: selectorIndex
  		ofObject: activeContext.
  	self pop: 1.
  	lookupClass := self fetchClassOf: newReceiver.
+ 	self sendBreakpoint: messageSelector receiver: newReceiver.
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (self lengthOf: messageSelector)
- 		receiver: newReceiver.
  	self findNewMethodInClass: lookupClass.
  
  	"Only test CompiledMethods for argument count - other objects will have to take their chances"
  	(self isCompiledMethod: newMethod)
  		ifTrue: [self success: (self argumentCountOf: newMethod) = argumentCount].
  
  	self successful
  		ifTrue: [self executeNewMethod.
  			"Recursive xeq affects successFlag"
  			self initPrimCall]
  		ifFalse: ["Slide the args back up (sigh) and re-insert the 
  			selector. "
  			1 to: argumentCount do: [:i | self
  						storePointer: argumentCount - i + 1 + selectorIndex
  						ofObject: activeContext
  						withValue: (self fetchPointer: argumentCount - i + selectorIndex ofObject: activeContext)].
  			self unPop: 1.
  			self storePointer: selectorIndex
  				ofObject: activeContext
  				withValue: messageSelector.
  			argumentCount := argumentCount + 1.
  			newMethod := performMethod.
  			messageSelector := performSelector]!

Item was changed:
  ----- Method: NewspeakInterpreter>>primitivePerformAt: (in category 'control primitives') -----
  primitivePerformAt: lookupClass
  	"Common routine used by perform:withArgs: and perform:withArgs:inSuperclass:"
  
  	"NOTE:  The case of doesNotUnderstand: is not a failure to perform.
  	The only failures are arg types and consistency of argumentCount."
  
  	| performSelector argumentArray arraySize index cntxSize performMethod performArgCount |
  	argumentArray := self stackTop.
  	(self isArray: argumentArray) ifFalse:[^self primitiveFail].
  
  	self successful ifTrue:
  		["Check for enough space in thisContext to push all args"
  		arraySize := self fetchWordLengthOf: argumentArray.
  		cntxSize := self fetchWordLengthOf: activeContext.
  		self success: (self stackPointerIndex + arraySize) < cntxSize].
  	self successful ifFalse: [^nil].
  
  	performSelector := messageSelector.
  	performMethod := newMethod.
  	performArgCount := argumentCount.
  	"pop the arg array and the selector, then push the args out of the array, as if they were on the stack"
  	self popStack.
  	messageSelector := self popStack.
  
  	"Copy the arguments to the stack, and execute"
  	index := 1.
  	[index <= arraySize] whileTrue:
  		[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
  		index := index + 1].
  	argumentCount := arraySize.
  
  	self fastLogSend: messageSelector.
+ 	self sendBreakpoint: messageSelector receiver: receiver.
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (self lengthOf: messageSelector)
- 		receiver: receiver.
  	self findNewMethodInClass: lookupClass.
  
  	"Only test CompiledMethods for argument count - any other objects playacting as CMs will have to take their chances"
  	(self isCompiledMethod: newMethod)
  		ifTrue: [self success: (self argumentCountOf: newMethod) = argumentCount].
  
  	self successful
  		ifTrue: [self executeNewMethod.  "Recursive xeq affects successFlag"
  				self initPrimCall]
  		ifFalse: ["Restore the state by popping all those array entries and pushing back the selector and array, and fail"
  				self pop: argumentCount.
  				self push: messageSelector.
  				self push: argumentArray.
  				messageSelector := performSelector.
  				newMethod := performMethod.
  				argumentCount := performArgCount]
  !

Item was added:
+ ----- Method: ObjectMemory>>firstFixedFieldOfMaybeImmediate: (in category 'debug support') -----
+ firstFixedFieldOfMaybeImmediate: oop
+ 	"for the message send breakpoint; selectors can be immediates."
+ 	<inline: false>
+ 	^(self isImmediate: oop)
+ 		ifTrue: [oop]
+ 		ifFalse: [self firstFixedField: oop]!

Item was added:
+ ----- Method: ObjectMemory>>lengthOfMaybeImmediate: (in category 'debug support') -----
+ lengthOfMaybeImmediate: oop
+ 	"for the message send breakpoint; selectors can be immediates."
+ 	<inline: false>
+ 	^(self isImmediate: oop)
+ 		ifTrue: [oop]
+ 		ifFalse: [self lengthOf: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>firstFixedFieldOfMaybeImmediate: (in category 'debug support') -----
+ firstFixedFieldOfMaybeImmediate: oop
+ 	"for the message send breakpoint; selectors can be immediates."
+ 	<inline: false>
+ 	^(self isImmediate: oop)
+ 		ifTrue: [oop]
+ 		ifFalse: [self firstFixedField: oop]!

Item was added:
+ ----- Method: SpurMemoryManager>>lengthOfMaybeImmediate: (in category 'debug support') -----
+ lengthOfMaybeImmediate: oop
+ 	"for the message send breakpoint; selectors can be immediates."
+ 	<inline: false>
+ 	^(self isImmediate: oop)
+ 		ifTrue: [oop]
+ 		ifFalse: [self lengthOf: oop]!

Item was changed:
  ----- Method: StackInterpreter>>commonSend (in category 'send bytecodes') -----
  commonSend
  	"Send a message, starting lookup with the receiver's class."
  	"Assume: messageSelector and argumentCount have been set, and that 
  	the receiver and arguments have been pushed onto the stack,"
  	"Note: This method is inlined into the interpreter dispatch loop."
  	<sharedCodeNamed: 'commonSend' inCase: #singleExtendedSendBytecode>
+ 	self sendBreakpoint: messageSelector receiver: (self internalStackValue: argumentCount).
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (objectMemory lengthOf: messageSelector)
- 		receiver: (self internalStackValue: argumentCount).
  	self printSends ifTrue:
  		[self printActivationNameForSelector: messageSelector startClass: lkupClass; cr].
  	self internalFindNewMethod.
  	self internalExecuteNewMethod.
  	self fetchNextBytecode!

Item was changed:
  ----- Method: StackInterpreter>>lookupMethodInClass: (in category 'message sending') -----
  lookupMethodInClass: class
  	| currentClass dictionary found |
  	<inline: false>
  	self assert: class ~= objectMemory nilObject.
  	currentClass := class.
  	[currentClass ~= objectMemory nilObject]
  		whileTrue:
  		[dictionary := objectMemory fetchPointer: MethodDictionaryIndex ofObject: currentClass.
  		dictionary = objectMemory nilObject ifTrue:
  			["MethodDict pointer is nil (hopefully due a swapped out stub)
  				-- raise exception #cannotInterpret:."
  			self createActualMessageTo: class.
  			messageSelector := objectMemory splObj: SelectorCannotInterpret.
+ 			self sendBreakpoint: messageSelector receiver: nil.
- 			self sendBreak: messageSelector + BaseHeaderSize
- 				point: (objectMemory lengthOf: messageSelector)
- 				receiver: nil.
  			^self lookupMethodInClass: (self superclassOf: currentClass)].
  		found := self lookupMethodInDictionary: dictionary.
  		found ifTrue: [^currentClass].
  		currentClass := self superclassOf: currentClass].
  
  	"Could not find #doesNotUnderstand: -- unrecoverable error."
  	messageSelector = (objectMemory splObj: SelectorDoesNotUnderstand) ifTrue:
  		[self error: 'Recursive not understood error encountered'].
  
  	"Cound not find a normal message -- raise exception #doesNotUnderstand:"
  	self createActualMessageTo: class.
  	messageSelector := objectMemory splObj: SelectorDoesNotUnderstand.
  	self sendBreak: messageSelector + BaseHeaderSize
  		point: (objectMemory lengthOf: messageSelector)
  		receiver: nil.
  	^self lookupMethodInClass: class!

Item was changed:
  ----- Method: StackInterpreter>>primitiveObject:perform:withArguments:lookedUpIn: (in category 'control primitives') -----
  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."
  
  	| 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 fetchWordLengthOf: 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 sendBreak: messageSelector + BaseHeaderSize
- 		point: (objectMemory lengthOf: messageSelector)
- 		receiver: actualReceiver.
  	self printSends ifTrue:
  		[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 := BytesPerWord * (performArgCount + 2). "+2 = receiver + saved newMethod"
  	argumentCount * BytesPerWord to: 0 by: BytesPerWord 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!

Item was added:
+ ----- Method: StackInterpreter>>sendBreakpoint:receiver: (in category 'debug support') -----
+ sendBreakpoint: selector receiver: receiver
+ 	<inline: true>
+ 	self sendBreak: (objectMemory firstFixedFieldOfMaybeImmediate: selector)
+ 		point: (objectMemory lengthOfMaybeImmediate: selector)
+ 		receiver: receiver!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitivePerform (in category 'control primitives') -----
  primitivePerform
  	<returnTypeC: #void>
  	| newReceiver lookupClassTag performMethod |
  	performMethod := newMethod.
  	messageSelector := self stackValue: argumentCount - 1.
  	newReceiver := self stackValue: argumentCount.
  
  	"NOTE: the following lookup may fail and be converted to #doesNotUnderstand:,
  	 so we must adjust argumentCount and slide args now, so that will work."
  
  	"Slide arguments down over selector"
  	argumentCount := argumentCount - 1.
  	argumentCount to: 1 by: -1 do:
  		[:i|
  		stackPages
  			longAt: stackPointer + (i * BytesPerWord)
  			put: (stackPages longAt: stackPointer + ((i - 1) * BytesPerWord))].
  	self pop: 1.
  	lookupClassTag := objectMemory fetchClassTagOf: newReceiver.
+ 	self sendBreakpoint: messageSelector receiver: newReceiver.
- 	self sendBreak: messageSelector + BaseHeaderSize
- 		point: (objectMemory lengthOf: messageSelector)
- 		receiver: newReceiver.
  	self printSends ifTrue:
  		[self printActivationNameForSelector: messageSelector
  			startClass: (objectMemory classForClassTag: lookupClassTag); cr].
  	self findNewMethodInClassTag: lookupClassTag.
  
  	"Only test CompiledMethods for argument count - other objects will have to take their chances"
  	((objectMemory isOopCompiledMethod: newMethod)
  	  and: [(self argumentCountOf: newMethod) = argumentCount]) ifFalse:
  		["Slide the args back up (sigh) and re-insert the selector."
  		self unPop: 1.
  		1 to: argumentCount by: 1 do:
  			[:i |
  			stackPages longAt: stackPointer + ((i - 1) * BytesPerWord)
  				put: (stackPages longAt: stackPointer + (i * BytesPerWord))].
  		stackPages longAt: stackPointer + (argumentCount * BytesPerWord) put: messageSelector.
  		argumentCount := argumentCount + 1.
  		newMethod := performMethod.
  		^self primitiveFail].
  
  	self executeNewMethod.
  	"Recursive xeq affects primErrorCode"
  	self initPrimCall!



More information about the Vm-dev mailing list