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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 19 23:44:16 UTC 2013


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

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

Name: VMMaker.oscog-eem.394
Author: eem
Time: 19 September 2013, 4:41:40.51 pm
UUID: ecd45400-0d67-4c39-9c8b-3210cf96a58b
Ancestors: VMMaker.oscog-eem.393

Rewrite send fault logic to do a 1st-level method lookup cache
probe after handling the send fault.  rename the handler to
handleForwardedSendFaultFor:.

Implement SMM>>byteSizeOf:.

Change the interpreter proxy API to include characterObjectOf:
and use it in FilePlugin>>primitiveDirectoryDelimitor.

Nuke unused method.

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

Item was changed:
  ----- Method: FilePlugin>>primitiveDirectoryDelimitor (in category 'directory primitives') -----
  primitiveDirectoryDelimitor
  	| ascii |
  	<export: true>
  	ascii := self asciiDirectoryDelimiter.
+ 	interpreterProxy minorVersion >= 13
+ 		ifTrue:
+ 			[interpreterProxy
+ 				pop: 1
+ 				thenPush: (interpreterProxy characterObjectOf: ascii)]
+ 		ifFalse:
+ 			[(ascii >= 0 and: [ascii <= 255])
+ 				ifTrue:
+ 					[interpreterProxy
+ 						pop: 1
+ 						thenPush: (interpreterProxy
+ 										fetchPointer: ascii
+ 										ofObject: interpreterProxy characterTable)]
+ 				ifFalse:
+ 					[interpreterProxy primitiveFail]]!
- 	((ascii >= 0) and: [ascii <= 255]) ifFalse:
- 		[^interpreterProxy primitiveFail].
- 	interpreterProxy
- 		pop: 1
- 		thenPush: (interpreterProxy fetchPointer: ascii ofObject: (interpreterProxy characterTable))!

Item was changed:
+ ----- Method: Spur32BitMMLESimulator>>booleanValueOf: (in category 'simulation only') -----
- ----- Method: Spur32BitMMLESimulator>>booleanValueOf: (in category 'C library simulation') -----
  booleanValueOf: obj
  	"hack around the CoInterpreter/ObjectMemory split refactoring"
  	^coInterpreter booleanValueOf: obj!

Item was added:
+ ----- Method: Spur32BitMMLESimulator>>ioLoadFunction:From: (in category 'simulation only') -----
+ ioLoadFunction: functionString From: pluginString
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter ioLoadFunction: functionString From: pluginString!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>is:KindOf: (in category 'simulation only') -----
- is: oop KindOf: classNameString
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^coInterpreter is: oop KindOf: classNameString!

Item was removed:
- ----- Method: Spur32BitMMLESimulator>>methodArgumentCount (in category 'simulation only') -----
- methodArgumentCount
- 	"hack around the CoInterpreter/ObjectMemory split refactoring"
- 	^coInterpreter methodArgumentCount!

Item was changed:
  ----- Method: SpurMemoryManager class>>vmProxyMinorVersion (in category 'simulation only') -----
  vmProxyMinorVersion
  	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^StackInterpreter vmProxyMinorVersion max: 13!
- 	^StackInterpreter vmProxyMinorVersion!

Item was added:
+ ----- Method: SpurMemoryManager>>byteSizeOf: (in category 'object access') -----
+ byteSizeOf: oop
+ 	<api>
+ 	| format |
+ 	(self isImmediate: oop) ifTrue: [^0].
+ 	format := self formatOf: oop.
+ 	format < self sixtyFourBitIndexableFormat ifTrue:
+ 		[^(self numSlotsOf: oop) << self shiftForWord].
+ 	format >= self firstByteFormat ifTrue:
+ 		[^(self numSlotsOf: oop) << self shiftForWord - (format bitAnd: 7)].
+ 	format >= self firstShortFormat ifTrue:
+ 		[^(self numSlotsOf: oop) << self shiftForWord - ((format bitAnd: 3) << 1)].
+ 	format >= self firstLongFormat ifTrue:
+ 		[^(self numSlotsOf: oop) << self shiftForWord - ((format bitAnd: 1) << 2)].
+ 	^(self numSlotsOf: oop) << self shiftForWord!

Item was added:
+ ----- Method: SpurMemoryManager>>interpreter (in category 'simulation') -----
+ interpreter
+ 	<doNotGenerate>
+ 	^coInterpreter!

Item was changed:
  ----- Method: SpurMemoryManager>>isIntegerObject: (in category 'object testing') -----
  isIntegerObject: oop
  	"This list records the valid senders of isIntegerObject: as we replace uses of
  	  isIntegerObject: by isImmediate: where appropriate."
  	(#(	DoIt
  		DoItIn:
  		makeBaseFrameFor:
  		quickFetchInteger:ofObject:
  		frameOfMarriedContext:
  		objCouldBeClassObj:
  		isMarriedOrWidowedContext:
  		shortPrint:
  		bytecodePrimAt
  		bytecodePrimAtPut
  		commonAt:
  		commonAtPut:
  		loadFloatOrIntFrom:
  		positive32BitValueOf:
  		primitiveExternalCall
  		checkedIntegerValueOf:
  		bytecodePrimAtPut
  		commonAtPut:
  		primitiveVMParameter
  		checkIsStillMarriedContext:currentFP:
  		displayBitsOf:Left:Top:Right:Bottom:
  		fetchStackPointerOf:
  		primitiveContextAt
  		primitiveContextAtPut
  		subscript:with:storing:format:
  		printContext:
  		compare31or32Bits:equal:
  		signed64BitValueOf:
  		primDigitMultiply:negative:
  		digitLength:
  		isNegativeIntegerValueOf:
  		magnitude64BitValueOf:
+ 		primitiveMakePoint
+ 		primitiveAsCharacter
+ 		primitiveInputSemaphore
+ 		baseFrameReturn
+ 		primitiveExternalCall) includes: thisContext sender method selector) ifFalse:
- 		primitiveMakePoint) includes: thisContext sender method selector) ifFalse:
  		[self halt].
  	^(oop bitAnd: 1) ~= 0!

Item was changed:
  ----- Method: StackInterpreter>>findNewMethodInClassTag: (in category 'message sending') -----
  findNewMethodInClassTag: classTag
  	"Find the compiled method to be run when the current 
  	messageSelector is sent to the given class, setting the values 
  	of 'newMethod' and 'primitiveIndex'."
  	| ok class |
  	<inline: false>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: classTag.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way "
+ 		[(objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
+ 			[lkupClassTag := self handleForwardedSendFaultFor: lkupClassTag.
+ 			ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
+ 			ok ifTrue:
+ 				[^nil]].
+ 		 class := objectMemory classForClassTag: classTag.
- 		[class := self sendFaultFor: classTag.
  		 self lookupMethodInClass: class.
  		 self addNewMethodToCache: class]!

Item was added:
+ ----- Method: StackInterpreter>>handleForwardedSendFaultFor: (in category 'message sending') -----
+ handleForwardedSendFaultFor: classTag
+ 	"Handle a send fault that may be due to a send to a forwarded object.
+ 	 Unforward the receiver on the stack and answer its actual class."
+ 	| rcvr |
+ 	(objectMemory isForwardedClassTag: classTag) ifFalse:
+ 		[^classTag].
+ 
+ 	rcvr := self stackValue: argumentCount.
+ 	"should *not* be a super send, so te receiver should be forwarded."
+ 	self assert: (objectMemory isOopForwarded: rcvr).
+ 	rcvr := objectMemory followForwarded: rcvr.
+ 	self stackValue: argumentCount put: rcvr.
+ 	self followForwardedFrameContents: framePointer
+ 		stackPointer: stackPointer + (argumentCount + 1 * BytesPerWord). "don't repeat effort"
+ 	(objectMemory isPointers: (self frameReceiver: framePointer)) ifTrue:
+ 		[objectMemory
+ 			followForwardedObjectFields: (self frameReceiver: framePointer)
+ 			toDepth: 0].
+ 	^objectMemory fetchClassTagOf: rcvr!

Item was changed:
  ----- Method: StackInterpreter>>iframeInstructionPointerForIndex:method: (in category 'frame access') -----
  iframeInstructionPointerForIndex: ip method: aMethod
  	"Answer the instruction pointer for use in an interpreter frame (a pointer to a bytecode)."
+ 	self assert: (ip between: (objectMemory lastPointerOf: aMethod) - 1
+ 					and: (objectMemory lengthOf: aMethod)).
+ 	^aMethod + ip + objectMemory baseHeaderSize - 2!
- 	self assert: (ip between: (objectMemory lastPointerOf: aMethod) and: (objectMemory lengthOf: aMethod)).
- 	^aMethod + ip + BaseHeaderSize - 2!

Item was changed:
  ----- Method: StackInterpreter>>internalFindNewMethod (in category 'message sending') -----
  internalFindNewMethod
  	"Find the compiled method to be run when the current messageSelector is sent to the class 'lkupClass', setting the values of 'newMethod' and 'primitiveIndex'."
  	| ok | 
  	<inline: true>
  	ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
  	ok ifFalse: "entry was not found in the cache; look it up the hard way"
  		[self externalizeIPandSP.
+ 		 (objectMemory isForwardedClassTag: lkupClassTag) ifTrue:
+ 			[lkupClassTag := self handleForwardedSendFaultFor: lkupClassTag.
+ 			ok := self lookupInMethodCacheSel: messageSelector classTag: lkupClassTag.
+ 			ok ifTrue:
+ 				[^nil]].
+ 		 lkupClass := objectMemory classForClassTag: lkupClassTag.
- 		 lkupClass := self sendFaultFor: lkupClassTag.
  		 self lookupMethodInClass: lkupClass.
  		 self internalizeIPandSP.
  		 self addNewMethodToCache: lkupClass]!

Item was removed:
- ----- Method: StackInterpreter>>sendFaultFor: (in category 'message sending') -----
- sendFaultFor: classTag
- 	"Handle a send fault that may be due to a send to a forwarded object.
- 	 Unforward the receiver on the stack and answer its actual class."
- 	| rcvr |
- 	(objectMemory isForwardedClassTag: classTag) ifFalse:
- 		[^objectMemory classForClassTag: classTag].
- 
- 	rcvr := self stackValue: argumentCount.
- 	"should *not* be a super send, so te receiver should be forwarded."
- 	self assert: (objectMemory isOopForwarded: rcvr).
- 	rcvr := objectMemory followForwarded: rcvr.
- 	self stackValue: argumentCount put: rcvr.
- 	self followForwardedFrameContents: framePointer
- 		stackPointer: stackPointer + (argumentCount + 1 * BytesPerWord). "don't repeat effort"
- 	(objectMemory isPointers: (self frameReceiver: framePointer)) ifTrue:
- 		[objectMemory
- 			followForwardedObjectFields: (self frameReceiver: framePointer)
- 			toDepth: 0].
- 	^objectMemory fetchClassOf: rcvr!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveSignalAtMilliseconds (in category 'system control primitives') -----
  primitiveSignalAtMilliseconds
  	"Cause the time semaphore, if one has been registered, to be
  	 signalled when the microsecond clock is greater than or equal to
  	 the given tick value. A tick value of zero turns off timer interrupts."
  	| msecsObj msecs deltaMsecs sema |
  	<var: #msecs type: #usqInt>
  	msecsObj := self stackTop.
  	sema := self stackValue: 1.
  	msecs := self positive32BitValueOf: msecsObj.
  	(self failed
+ 	 or: [objectMemory isImmediate: sema]) ifTrue:
- 	 or: [objectMemory isIntegerObject: sema]) ifTrue:
  		[self primitiveFail.
  		 ^nil].
  	(objectMemory fetchClassOfNonImm: sema) = (objectMemory splObj: ClassSemaphore)
  		ifTrue:
  			[objectMemory splObj: TheTimerSemaphore put: sema.
  			deltaMsecs := msecs - (self ioMSecs bitAnd: MillisecondClockMask).
  			deltaMsecs < 0 ifTrue:
  				[deltaMsecs := deltaMsecs + MillisecondClockMask + 1].
  			nextWakeupUsecs := self ioUTCMicroseconds + (deltaMsecs * 1000)]
  		ifFalse:
  			[objectMemory
  				storePointer: TheTimerSemaphore
  				ofObject: objectMemory specialObjectsOop
  				withValue: objectMemory nilObject.
  			nextWakeupUsecs := 0].
  	self pop: 2!

Item was added:
+ ----- Method: StackInterpreterSimulator>>imageName (in category 'spur bootstrap') -----
+ imageName
+ 	^imageName!

Item was added:
+ ----- Method: StackInterpreterSimulator>>imageName: (in category 'spur bootstrap') -----
+ imageName: aString
+ 	imageName := aString!

Item was removed:
- ----- Method: VMClass class>>emitInterpreterProxyVersionOn: (in category 'api version') -----
- emitInterpreterProxyVersionOn: aStream 
- 	aStream
- 		nextPutAll: '#define VM_PROXY_MAJOR '; print: self vmProxyMajorVersion; cr;
- 		nextPutAll: '#define VM_PROXY_MINOR '; print: self vmProxyMinorVersion; cr; cr!



More information about the Vm-dev mailing list