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

commits at source.squeak.org commits at source.squeak.org
Fri Jan 24 21:00:34 UTC 2014


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

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

Name: VMMaker.oscog-eem.591
Author: eem
Time: 24 January 2014, 12:57:20.086 pm
UUID: 2f605da3-babd-4f62-a19e-085c28cca416
Ancestors: VMMaker.oscog-eem.590

Fix the regression in CoInterpreter>>validInstructionPointer:inMethod:framePointer:
by accepting an instruction pointer pointing just before the first
bytecode in StackInterpreter>>validInstructionPointer:inMethod:framePointer:
and reverting CoInterpreter's method.

Add some missing simulation redirects.

Copy the filterPerfrmOf:to: hack to StackInterpreterSimulator.

Don't bother emitting plugins for the Newspeak stack VM.

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

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 addressCouldBeOop: rcvr).
  	self sendBreakpoint: selector receiver: rcvr.
  	mClassMixin := self mMethodClass.
  	mixinApplication := self 
  							findApplicationOfTargetMixin: mClassMixin
  							startingAtBehavior: (objectMemory fetchClassOf: rcvr).
  	self assert: (objectMemory lengthOf: mixinApplication) > (InstanceSpecificationIndex + 1).
+ 	classTag := objectMemory classTagForClass: (self superclassOf: mixinApplication).
- 	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:
  			[(objectMemory isOopForwarded: selector) ifTrue:
  				[^self
  					ceDynamicSuperSend: (self handleForwardedSelectorFaultFor: selector)
  					to: rcvr
  					numArgs: numArgs].
  			 (objectMemory isForwardedClassTag: classTag) ifTrue:
  				[^self
  					ceDynamicSuperSend: selector
  					to: (self handleForwardedSendFaultForReceiver: rcvr stackDelta: 1 "skip return pc")
  					numArgs: numArgs].
  			 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>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
  validInstructionPointer: instrPointer inMethod: aMethod framePointer: fp
  	<var: #instrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
  	<var: #fp type: #'char *'>
  	| theInstrPointer cogMethod |
  	<var: #theInstrPointer type: #usqInt>
  	<var: #cogMethod type: #'CogMethod *'>
  	instrPointer = cogit ceCannotResumePC ifTrue:
  		[^self isMachineCodeFrame: fp].
  	instrPointer = cogit ceReturnToInterpreterPC
  		ifTrue:
  			[(self isMachineCodeFrame: fp) ifTrue:
  				[^false].
  			 theInstrPointer := self iframeSavedIP: fp]
  		ifFalse:
+ 			[theInstrPointer := instrPointer.
- 			[theInstrPointer := instrPointer + 1.
  			self cppIf: NewspeakVM
  				ifTrue:
  					[(self isMachineCodeFrame: fp) ifTrue:
  						[cogMethod := self mframeHomeMethod: fp.
  						 ^theInstrPointer >= (cogMethod asUnsignedInteger + (cogit sizeof: CogMethod))
  						   and: [theInstrPointer < (cogMethod asUnsignedInteger + cogMethod blockSize)]]]
  				ifFalse:
  					[| header |
  					 header := self rawHeaderOf: aMethod.
  					 ((self isCogMethodReference: header)
  					   and: [theInstrPointer < objectMemory startOfMemory]) ifTrue:
  					 	[cogMethod := self cCoerceSimple: header to: #'CogMethod *'.
  					 	 ^theInstrPointer >= (header + (cogit sizeof: CogMethod))
  					 	 and: [theInstrPointer < (header + cogMethod blockSize)]]]].
  	^super validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>methodReturnValue: (in category 'simulation only') -----
+ methodReturnValue: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter methodReturnValue: oop!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>signed32BitIntegerFor: (in category 'simulation only') -----
+ signed32BitIntegerFor: integerValue
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter signed32BitIntegerFor: integerValue!

Item was added:
+ ----- Method: SpurMemoryManager>>methodReturnValue: (in category 'simulation only') -----
+ methodReturnValue: oop
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter methodReturnValue: oop!

Item was added:
+ ----- Method: SpurMemoryManager>>signed32BitIntegerFor: (in category 'simulation only') -----
+ signed32BitIntegerFor: integerValue
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	<doNotGenerate>
+ 	^coInterpreter signed32BitIntegerFor: integerValue!

Item was changed:
  ----- Method: StackInterpreter>>validInstructionPointer:inMethod:framePointer: (in category 'debug support') -----
  validInstructionPointer: theInstrPointer inMethod: aMethod framePointer: fp
  	<var: #theInstrPointer type: #usqInt>
  	<var: #aMethod type: #usqInt>
  	<var: #fp type: #'char *'>
  	^self
  		cppIf: MULTIPLEBYTECODESETS
  		ifTrue:
  			[| methodHeader |
  			 methodHeader := self noAssertHeaderOf: aMethod. "-1 for pre-increment in fetchNextBytecode"
+ 			 theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop - 1)
- 			 theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop)
  			 and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + BaseHeaderSize - 1)
  			 and: ["If the method starts with a CallPrimitive opcode the instruction pointer should be past it."
  				((self headerIndicatesAlternateBytecodeSet: methodHeader)
+ 				  and: [(self alternateHeaderHasPrimitiveFlag: methodHeader)
+ 				  and: [theInstrPointer < (aMethod
+ 										+ BytesPerOop - 1
- 				and: [(self alternateHeaderHasPrimitiveFlag: methodHeader)
- 				and: [theInstrPointer < (aMethod
- 										+ BaseHeaderSize - 1
  										+ (objectMemory lastPointerOf: aMethod)
+ 										+ (self sizeOfCallPrimitiveBytecode: methodHeader))]])
- 										+ (self sizeOfCallPrimitiveBytecode: methodHeader) - 1)]])
  					not]]]
  		ifFalse: "-1 for pre-increment in fetchNextBytecode"
+ 			[theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop - 1)
- 			[theInstrPointer >= (aMethod + (objectMemory lastPointerOf: aMethod) + BytesPerOop)
  			 and: [theInstrPointer < (aMethod + (objectMemory byteLengthOf: aMethod) + objectMemory baseHeaderSize - 1)]]!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'bootstrapping byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters'
- 	instanceVariableNames: 'bootstrapping byteCount breakCount sendCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-InterpreterSimulation'!
  
  !StackInterpreterSimulator commentStamp: 'eem 9/3/2013 11:05' prior: 0!
  This class defines basic memory access and primitive simulation so that the StackInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(StackInterpreterSimulator new openOn: Smalltalk imageName) test
  
  	((StackInterpreterSimulator newWithOptions: #(NewspeakVM true MULTIPLEBYTECODESETS true))
  		openOn: 'ns101.image') test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example of what Eliot uses to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  | vm |
  vm := StackInterpreterSimulator newWithOptions: #().
  vm openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'.
  vm setBreakSelector: #&.
  vm openAsMorph; run!

Item was added:
+ ----- Method: StackInterpreterSimulator>>filterPerformOf:to: (in category 'control primitives') -----
+ filterPerformOf: selector to: receiver
+ 	"This is to allow simulator to filter start-up items to avoid as-yet unsimulatable plugins."
+ 	performFilters ifNil: [^false].
+ 	(performFilters at: (self shortPrint: receiver) ifAbsent: []) ifNotNil:
+ 		[:messages|
+ 		^messages includes: (self stringOf: selector)].
+ 	^false!

Item was added:
+ ----- Method: StackInterpreterSimulator>>forShortPrintString:filterPerformMessages: (in category 'control primitives') -----
+ forShortPrintString: shortPrintString filterPerformMessages: aCollection
+ 	performFilters ifNil:
+ 		[performFilters := Dictionary new].
+ 	performFilters at: shortPrintString put: aCollection!

Item was added:
+ ----- Method: StackInterpreterSimulator>>primitiveObject:perform:withArguments:lookedUpIn: (in category 'control primitives') -----
+ primitiveObject: actualReceiver perform: selector withArguments: argumentArray lookedUpIn: lookupClass
+ 	"Override to allow simulator to filter start-up items to avoid as-yet unsimulatable plugins."
+ 
+ 	(self filterPerformOf: selector to: actualReceiver) ifTrue:
+ 		[^self pop: argumentCount + 1 thenPush: actualReceiver].
+ 	^super primitiveObject: actualReceiver perform: selector withArguments: argumentArray lookedUpIn: lookupClass!

Item was added:
+ ----- Method: StackInterpreterSimulator>>primitivePerform (in category 'debugging traps') -----
+ primitivePerform
+ 	| selector |
+ 	selector := self stackValue: argumentCount - 1.
+ 	self sendBreakpoint: selector receiver: (self stackValue: argumentCount).
+ 	(self filterPerformOf: selector to: (self stackValue: argumentCount)) ifTrue:
+ 		[^self pop: argumentCount].
+ 	^super primitivePerform!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakStackVM (in category 'configurations') -----
  generateNewspeakStackVM
+ 	"No primitives since we can use those for the Cog Newspeak VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(NewspeakVM true MULTIPLEBYTECODESETS true)
  		to: (FileDirectory default pathFromURI: 'oscogvm/nsstacksrc')
  		platformDir: (FileDirectory default pathFromURI: 'oscogvm/platforms')
+ 		excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
- 		including:#(	AsynchFilePlugin BMPReadWriterPlugin BalloonEnginePlugin BitBltSimulation DSAPlugin DropPlugin
- 					FileCopyPlugin FilePlugin FloatArrayPlugin FloatMathPlugin InflatePlugin JPEGReadWriter2Plugin
- 					JPEGReaderPlugin LargeIntegersPlugin Matrix2x3Plugin MiscPrimitivePlugin NewsqueakIA32ABIPlugin
- 					RePlugin SecurityPlugin SocketPlugin SoundPlugin SurfacePlugin SqueakSSLPlugin ThreadedIA32FFIPlugin
- 					UUIDPlugin UnixOSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin Win32OSProcessPlugin)!



More information about the Vm-dev mailing list