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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 12 03:00:28 UTC 2015


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

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

Name: VMMaker.oscog-eem.1086
Author: eem
Time: 11 March 2015, 7:58:35.196 pm
UUID: 799f97ec-7ee7-4b82-adf2-43302136c3f8
Ancestors: VMMaker.oscog-eem.1085

Simulation:
Fix regression in simulator's isScreenSize.

Implement simulation of translated primitives that
don't access inst vars (the bitmap (de)compression
and string primitives).  So that the machinery can
match actual selectors with primitive selectors
have a TMethod remember the original selector of
a translated primitive TMethod in properties.

Add an assert to InterpreterStackPages>>longAt:put:
to prevent storing garbage there-in when there's
a bug.

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

Item was added:
+ ----- Method: CCodeGenerator>>baseTypeForPointerType: (in category 'utilities') -----
+ baseTypeForPointerType: aCType
+ 	"Answer the type of the referent of a pointer type."
+ 	self assert: aCType last == $*.
+ 	^self baseTypeForType: aCType allButLast!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter 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.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) 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 to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	cogit numRegArgs > 0 ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	"Note: we must initialize ConstMinusOne & HasBeenReturnedFromMCPC differently
  	 for simulation, due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  	HasBeenReturnedFromMCPC := objectMemory integerObjectOf: -1.
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := desiredCogCodeSize := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^ self].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
+ 	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
- 	displayForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
  	extSemTabSize := 256!

Item was changed:
  ----- Method: CogVMSimulator>>ioScreenSize (in category 'I/O primitives support') -----
  ioScreenSize
+ 	"Answer the screen extent packed into 32 bits.  In the simulator,
+ 	 displayForm gets initialized with a fake form; don't be deceived."
+ 	| extent |
+ 	extent := (displayForm notNil and: [displayForm ~~ fakeForm])
+ 				ifTrue: [displayForm extent]
+ 				ifFalse: [self desiredDisplayExtent].
+ 	^extent x << 16 + extent y!
- 	"Return the screen extent packed into 32 bits."
- 
- 	^displayForm
- 		ifNotNil: [(displayForm width << 16) + displayForm height]
- 		ifNil: [savedWindowSize ifNil: 640 << 16 + 480]!

Item was changed:
  VMClass subclass: #InterpreterPlugin
+ 	instanceVariableNames: 'interpreterProxy moduleName translatedMethodCache'
- 	instanceVariableNames: 'interpreterProxy moduleName'
  	classVariableNames: ''
  	poolDictionaries: 'VMBasicConstants'
  	category: 'VMMaker-Plugins'!
  
  !InterpreterPlugin commentStamp: 'tpr 5/5/2003 11:43' prior: 0!
  This class provides the basic framework for creating VM plugins. Most of the useful methods are on the class side; particularly take note of the messages like #shouldBeTranslated and #requiresPlatformFiles.!

Item was added:
+ ----- Method: InterpreterPlugin class>>browseTranslatedPrimitives (in category 'translated primitives') -----
+ browseTranslatedPrimitives
+ 	"InterpreterPlugin browseTranslatedPrimitives"
+ 	| methodRefs |
+ 	methodRefs := OrderedCollection new.
+ 	self withAllSubclasses do:
+ 		[:class|
+ 		methodRefs addAll:
+ 			(class translatedPrimitives collect:
+ 				[:tuple|
+ 				(self methodForTranslatedPrimitiveTuple: tuple) methodReference])].
+ 	self systemNavigation browseMessageList: methodRefs
+ 		name: 'Translated primitives'!

Item was changed:
  ----- Method: InterpreterPlugin class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Note: This method must be implemented by all subclasses to declare variables."
  
  	aCCodeGenerator 
+ 		var: #interpreterProxy type: #'struct VirtualMachine*';
+ 		removeVariable: 'translatedMethodCache'.
- 		var: #interpreterProxy 
- 		type: #'struct VirtualMachine*'.
  	self declareHeaderFilesIn: aCCodeGenerator.!

Item was added:
+ ----- Method: InterpreterPlugin class>>methodForTranslatedPrimitiveTuple: (in category 'translated primitives') -----
+ methodForTranslatedPrimitiveTuple: tuple
+ 	| class |
+ 	class := Smalltalk classNamed: tuple first.
+ 	^class
+ 		compiledMethodAt: tuple last
+ 		ifAbsent: [class class compiledMethodAt: tuple last]!

Item was added:
+ ----- Method: InterpreterPlugin class>>methodOrNilForTranslatedPrimitiveSelector: (in category 'translated primitives') -----
+ methodOrNilForTranslatedPrimitiveSelector: selector
+ 	self translatedPrimitives do:
+ 		[:tuple| | method |
+ 		method := self methodForTranslatedPrimitiveTuple: tuple.
+ 		method pragmas do:
+ 			[:p|
+ 			((p keyword beginsWith: 'primitive:') and: [p arguments first = selector]) ifTrue:
+ 				[^method]]].
+ 	^nil!

Item was added:
+ ----- Method: InterpreterPlugin>>doesNotUnderstand: (in category 'simulation support') -----
+ doesNotUnderstand: aMessage
+ 	<doNotGenerate>
+ 	"Override doesNotUnderstand: to iuntercept sends of translated primitive selectors.
+ 	 The translated primitives are primitives derived from the primitive methods themselves
+ 	 translating their failure code/method body into Slang code."
+ 	(self methodAndTypesOrNilForTranslatedPrimitiveSelector: aMessage selector)
+ 		ifNil: [^super doesNotUnderstand: aMessage]
+ 		ifNotNil:
+ 			[:tuple| | method |
+ 			 method := tuple first.
+ 			 tuple second
+ 				ifNil: [interpreterProxy primitiveFail]
+ 				ifNotNil:
+ 					[:types|
+ 					 self tryToRunTranslatedPrimitive: method types: types subsidiaries: tuple third].
+ 			(#(	compare:with:collated:
+ 				findFirstInString:inSet:startingAt:
+ 				findSubstring:in:startingAt:matchTable:
+ 				hashBytes:startingWith:
+ 				indexOfAscii:inString:startingAt:
+ 				translate:from:to:table:
+ 				compress:toByteArray:
+ 				decompress:fromByteArray:at:)
+ 					includes: method selector) ifFalse:
+ 				[interpreterProxy transcript print: method; cr.
+ 				 interpreterProxy coInterpreter printExternalHeadFrame].
+ 			 interpreterProxy failed ifTrue:
+ 				[interpreterProxy transcript
+ 					nextPutAll: 'WARNING!! Failing translated primitive ';
+ 					nextPutAll: aMessage selector;
+ 					nextPutAll: ' implemented by ';
+ 					nextPutAll: method methodClass name;
+ 					nextPutAll: '>>';
+ 					nextPutAll: method selector;
+ 					cr;
+ 					flush]]!

Item was added:
+ ----- Method: InterpreterPlugin>>executeTranslatedPrimitiveMethod:arguments:subsidiaries: (in category 'simulation support') -----
+ executeTranslatedPrimitiveMethod: method arguments: args subsidiaries: subsidiaryMethods
+ 	<doNotGenerate>
+ 	"Execute the method within a doesNotUnderstand: handler that will
+ 	 catch sends of asciiValue and evaluate any subsidiary methods.."
+ 	^[interpreterProxy withArgs: args executeMethod: method]
+ 		on: MessageNotUnderstood
+ 		do: [:ex|
+ 			ex receiver == interpreterProxy ifTrue:
+ 				[ex resume:
+ 					(self executeTranslatedPrimitiveMethod:
+ 							(subsidiaryMethods
+ 								at: ex message selector
+ 								ifAbsent: [ex pass])
+ 						arguments: ex message arguments
+ 						subsidiaries: subsidiaryMethods)].
+ 			(ex receiver isInteger
+ 			and: [ex message selector == #asciiValue]) ifTrue:
+ 				[ex resume: ex receiver].
+ 			ex pass]!

Item was added:
+ ----- Method: InterpreterPlugin>>methodAndTypesOrNilForTranslatedPrimitiveSelector: (in category 'simulation') -----
+ methodAndTypesOrNilForTranslatedPrimitiveSelector: selector
+ 	<doNotGenerate>
+ 	"If selector maps to a simulateable translated primitive method, then
+ 	 answer the method and its types for selector, the selector of a translated primitive.
+ 	 Otherwise answer nil.  This caches the results of analysis in translatedMethodCache."
+ 	translatedMethodCache ifNil:
+ 		[translatedMethodCache := IdentityDictionary new.
+ 		 translatedMethodCache at: #CCodeGenerator put: CCodeGenerator new].
+ 	^translatedMethodCache
+ 		at: selector
+ 		ifAbsentPut: [self tupleOrNilForTranslatedPrimitiveSelector: selector]!

Item was added:
+ ----- Method: InterpreterPlugin>>methodWithoutPrimitive: (in category 'simulation') -----
+ methodWithoutPrimitive: method
+ 	"Answer either aMethod or a copy of aMehtod, such that the result does /not/ have a primitive."
+ 	<doNotGenerate>
+ 	| mn properties newProperties |
+ 	method primitive = 0 ifTrue:
+ 		[^method].
+ 	mn := method methodNode.
+ 	properties := mn properties.
+ 	newProperties := properties copy.
+ 	properties pragmas do:
+ 		[:pragma|
+ 		(pragma keyword beginsWith: #primitive:) ifTrue:
+ 			[newProperties := newProperties copyWithout: pragma]].
+ 	^mn
+ 		instVarNamed: 'primitive' put: 0;
+ 		instVarNamed: 'properties' put: newProperties;
+ 		generate: method trailer using: method class!

Item was added:
+ ----- Method: InterpreterPlugin>>translatedPrimitiveArgument:ofType:using: (in category 'simulation') -----
+ translatedPrimitiveArgument: index ofType: cTypeString using: aCCodeGenerator
+ 	| oop |
+ 	oop := interpreterProxy stackValue: interpreterProxy methodArgumentCount - index.
+ 	cTypeString last == $* ifTrue:
+ 		[^ObjectProxyForTranslatedPrimitiveSimulation new
+ 			interpreter: interpreterProxy
+ 			oop: oop
+ 			unitSize: (self sizeof: (aCCodeGenerator baseTypeForPointerType: cTypeString) asSymbol)].
+ 	((interpreterProxy isIntegerObject: oop)
+ 	 and: [aCCodeGenerator isIntegralCType: cTypeString]) ifTrue:
+ 		[^interpreterProxy integerValueOf: oop].
+ 	self halt!

Item was added:
+ ----- Method: InterpreterPlugin>>tryToRunTranslatedPrimitive:types:subsidiaries: (in category 'simulation') -----
+ tryToRunTranslatedPrimitive: method types: types subsidiaries: subsidiaryMethods
+ 	"Evaluate a translated primitive method using the receiver as its receiver.
+ 	 Supply integers or proxies for the arguments as necessary."
+ 	<doNotGenerate>
+ 	| cg args result |
+ 	interpreterProxy methodArgumentCount ~= method numArgs ifTrue:
+ 		[^interpreterProxy primitiveFail].
+ 	cg := translatedMethodCache at: #CCodeGenerator.
+ 	args := (1 to: method numArgs)
+ 				with: types
+ 				collect:
+ 					[:i :type |
+ 					 (self translatedPrimitiveArgument: i ofType: type using: cg) ifNil:
+ 						[^interpreterProxy primitiveFail]].
+ 	result := self executeTranslatedPrimitiveMethod: method arguments: args subsidiaries: subsidiaryMethods.
+ 	interpreterProxy failed ifFalse:
+ 		[result == interpreterProxy
+ 			ifTrue: [interpreterProxy pop: interpreterProxy methodArgumentCount]
+ 			ifFalse:
+ 				[result isInteger
+ 					ifTrue: [interpreterProxy methodReturnValue: (interpreterProxy integerObjectOf: result)]
+ 					ifFalse: [self halt]]]!

Item was added:
+ ----- Method: InterpreterPlugin>>tupleOrNilForTranslatedPrimitiveSelector: (in category 'simulation') -----
+ tupleOrNilForTranslatedPrimitiveSelector: selector
+ 	"Answer a tuple of method, types, subsidiary methods, for the selector of a translated
+ 	 primitive.  If the method cannot be simulated, for example if it accesses instance
+ 	 variables, answer a tuple whose types element is nil."
+ 	<doNotGenerate>
+ 	^(self class methodOrNilForTranslatedPrimitiveSelector: selector) ifNotNil:
+ 		[:method| | argNames argPragmas cg types subsidiaryMethods |
+ 		"Since the plugin itself runs the method, and the method is on some
+ 		 distant class, if the method accesses inst vars, the mechanism can't work."
+ 		method hasInstVarRef ifTrue: [^{method. nil. nil}].
+ 		argNames := [method methodClass newParser parseParameterNames: method getSourceFromFile]
+ 						on: Error
+ 						do: [:ex|
+ 							^{method. nil. nil}].
+ 		argPragmas := method pragmas select:
+ 							[:p|
+ 							(p keyword beginsWith: 'var:')
+ 							and: [argNames includes: p arguments first]].
+ 		cg := translatedMethodCache at: #CCodeGenerator.
+ 		types := (1 to: method numArgs) collect:
+ 					[:i|
+ 					(argPragmas detect: [:p| p arguments first = (argNames at: i)] ifNone: [])
+ 						ifNil: [#sqInt]
+ 						ifNotNil:
+ 							[:pragma|
+ 							cg extractTypeFor: (argNames at: i) fromDeclaration: pragma arguments second]].
+ 		 "Subsidiary methods are typically implemented for the primitive method only."
+ 		 subsidiaryMethods :=
+ 			method messages
+ 				select:
+ 					[:subsidiary|
+ 					 (method methodClass includesSelector: subsidiary)
+ 					 and: [(Object includesSelector: subsidiary) not]]
+ 				thenCollect:
+ 					[:subsidiary| | subsidiaryMethod |
+ 					subsidiaryMethod := method methodClass >> subsidiary.
+ 					subsidiaryMethod hasInstVarRef ifTrue:
+ 						[^{method. nil. nil}].
+ 					subsidiaryMethod].
+ 		 { self methodWithoutPrimitive: method.
+ 		   types.
+ 		   Dictionary withAll:
+ 			(subsidiaryMethods collect:
+ 				[:m| m selector -> (self methodWithoutPrimitive: m)])}]!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitivePointX (in category 'object access primitives') -----
- primitivePointX
- 	| rcvr | 
- 	<inline: false>
- 	rcvr := self popStack.
- 	self assertClassOf: rcvr is: (objectMemory splObj: ClassPoint).
- 	self successful
- 		ifTrue: [self push: (objectMemory fetchPointer: XIndex ofObject: rcvr)]
- 		ifFalse: [self unPop: 1]!

Item was removed:
- ----- Method: InterpreterPrimitives>>primitivePointY (in category 'object access primitives') -----
- primitivePointY
- 	| rcvr | 
- 	<inline: false>
- 	rcvr := self popStack.
- 	self assertClassOf: rcvr is: (objectMemory splObj: ClassPoint).
- 	self successful
- 		ifTrue: [self push: (objectMemory fetchPointer: YIndex ofObject: rcvr)]
- 		ifFalse: [self unPop: 1]!

Item was changed:
  ----- Method: InterpreterStackPages>>longAt:put: (in category 'memory access') -----
  longAt: byteAddress put: a32BitValue
  	<doNotGenerate>
  	"Note: Adjusted for Smalltalk's 1-based array indexing."
+ 	self assert: a32BitValue isInteger.
  	self assert: (byteAddress bitAnd: objectMemory wordSize - 1) == 0.
  	^stackMemory at: byteAddress // objectMemory wordSize + indexOffset put: a32BitValue!

Item was added:
+ Object subclass: #ObjectProxyForTranslatedPrimitiveSimulation
+ 	instanceVariableNames: 'interpreter oop unitSize'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-InterpreterSimulation'!
+ 
+ !ObjectProxyForTranslatedPrimitiveSimulation commentStamp: 'eem 3/11/2015 19:58' prior: 0!
+ An ObjectProxyForTranslatedPrimitiveSimulation is a wrapper for an object on the simulated heap that allows that "object" to be accessed from within a simulating translated primitive such as Bitmap>>compress:toByteArray:.
+ 
+ Instance Variables
+ 	interpreter:		<ObjectMemory|SpurMemoryManager>
+ 	oop:			<Integer>
+ 	unitSize:		<Integer>
+ 
+ interpreter
+ 	- the object memory class being used as the simulator's interpreterProxy
+ 
+ oop
+ 	- the oop of the "object" being wrapped
+ 
+ unitSize
+ 	- 1, 2, 4 or 8
+ !

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>at: (in category 'accessing') -----
+ at: index
+ 	self assert: (index between: 1 and: self size).
+ 	unitSize = 1 ifTrue: [^interpreter fetchByte: index - 1 ofObject: oop].
+ 	unitSize = 2 ifTrue: [^interpreter fetchShort16: index - 1 ofObject: oop].
+ 	unitSize = 4 ifTrue: [^interpreter fetchLong32: index - 1 ofObject: oop].
+ 	unitSize = 8 ifTrue: [^interpreter fetchLong64: index - 1 ofObject: oop].
+ 	self halt: 'Can''t handle unitSize ', unitSize printString!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>at:put: (in category 'accessing') -----
+ at: index put: val
+ 	self assert: (index between: 1 and: self size).
+ 	unitSize = 1 ifTrue: [^ interpreter storeByte: index - 1 ofObject: oop withValue: val].
+ 	unitSize = 2 ifTrue: [^ interpreter storeShort16: index - 1 ofObject: oop withValue: val].
+ 	unitSize = 4 ifTrue: [^ interpreter storeLong32: index - 1 ofObject: oop withValue: val].
+ 	unitSize = 8 ifTrue: [^ interpreter storeLong64: index - 1 ofObject: oop withValue: val].
+ 	self halt: 'Can''t handle unitSize ', unitSize printString!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>basicAt: (in category 'accessing') -----
+ basicAt: offset
+ 	^self at: offset!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>basicAt:put: (in category 'accessing') -----
+ basicAt: offset put: val
+ 	^self at: offset put: val!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>basicSize (in category 'accessing') -----
+ basicSize
+ 	^self size!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>interpreter (in category 'accessing') -----
+ interpreter
+ 
+ 	^ interpreter!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>interpreter: (in category 'accessing') -----
+ interpreter: anObject
+ 
+ 	interpreter := anObject!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>interpreter:oop:unitSize: (in category 'initialize-release') -----
+ interpreter:  anInterpreter oop: objOop unitSize: baseTypeSize
+ 	interpreter := anInterpreter.
+ 	oop := objOop.
+ 	unitSize := baseTypeSize!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>oop (in category 'accessing') -----
+ oop
+ 
+ 	^ oop!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>oop: (in category 'accessing') -----
+ oop: anObject
+ 
+ 	oop := anObject!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>size (in category 'accessing') -----
+ size
+ 	unitSize = 1 ifTrue: [^interpreter numBytesOf: oop].
+ 	unitSize = 2 ifTrue: [^interpreter num16BitUnitsOf: oop].
+ 	unitSize = 4 ifTrue: [^interpreter num32BitUnitsOf: oop].
+ 	unitSize = 8 ifTrue: [^interpreter num64BitUnitsOf: oop].
+ 	self halt: 'Can''t handle unitSize ', unitSize printString!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>unitSize (in category 'accessing') -----
+ unitSize
+ 
+ 	^ unitSize!

Item was added:
+ ----- Method: ObjectProxyForTranslatedPrimitiveSimulation>>unitSize: (in category 'accessing') -----
+ unitSize: anObject
+ 
+ 	unitSize := anObject!

Item was changed:
  StackInterpreterPrimitives subclass: #StackInterpreterSimulator
+ 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm fakeForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
- 	instanceVariableNames: 'parent bootstrapping byteCount breakCount sendCount lookupCount printSends printReturns traceOn myBitBlt displayForm filesOpen imageName pluginList mappedPluginEntries quitBlock transcript displayView printFrameAtEachStep printBytecodeAtEachStep systemAttributes startMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize atEachStepBlock disableBooleanCheat performFilters eventQueue assertVEPAES'
  	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 changed:
  ----- Method: StackInterpreterSimulator>>initialize (in category 'initialization') -----
  initialize
  	"Initialize the StackInterpreterSimulator when running the interpreter
  	 inside Smalltalk. The primary responsibility of this method is to allocate
  	 Smalltalk Arrays for variables that will be declared as statically-allocated
  	 global arrays in the translated code."
  	super initialize.
  
  	bootstrapping := false.
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	objectMemory coInterpreter: self.
  
  	"Note: we must initialize ConstMinusOne differently for simulation,
  		due to the fact that the simulator works only with +ve 32-bit values"
  	ConstMinusOne := objectMemory integerObjectOf: -1.
  
  	methodCache := Array new: MethodCacheSize.
  	atCache := Array new: AtCacheTotalSize.
  	self flushMethodCache.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	mappedPluginEntries := OrderedCollection new.
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[primitiveAccessorDepthTable := Array new: primitiveTable size.
  			 pluginList := {}.
  			 self loadNewPlugin: '']
  		ifFalse:
  			[pluginList := {'' -> self }].
  	desiredNumStackPages := desiredEdenBytes := 0.
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := Time totalSeconds * 1000000.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := sendCount := lookupCount := 0.
  	quitBlock := [^self].
  	traceOn := true.
  	printSends := printReturns := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
+ 	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
- 	displayForm := 'Display has not yet been installed' asDisplayText form.
  	eventQueue := SharedQueue new.
  	suppressHeartbeatFlag := false.
  	systemAttributes := Dictionary new.
  	extSemTabSize := 256.
  	disableBooleanCheat := false.
  	assertVEPAES := true. "a flag so the assertValidExecutionPointers can be disabled for simulation speed"!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ioScreenSize (in category 'I/O primitives support') -----
  ioScreenSize
+ 	"Answer the screen extent packed into 32 bits.  In the simulator,
+ 	 displayForm gets initialized with a fake form; don't be deceived."
+ 	| extent |
+ 	extent := (displayForm notNil and: [displayForm ~~ fakeForm])
+ 				ifTrue: [displayForm extent]
+ 				ifFalse: [self desiredDisplayExtent].
+ 	^extent x << 16 + extent y!
- 	"Return the screen extent packed into 32 bits."
- 
- 	^displayForm
- 		ifNotNil: [(displayForm width << 16) + displayForm height]
- 		ifNil: [savedWindowSize ifNil: 640 << 16 + 480]!

Item was changed:
  ----- Method: TMethod>>preparePrimitiveName (in category 'primitive compilation') -----
  preparePrimitiveName
+ 	"Prepare the selector for this method in translation.
+ 	 Remember the original selector in properties."
- 	"Prepare the selector for this method in translation"
  	| aClass |
+ 	properties := properties copy.
+ 	properties selector: selector.
  	aClass := definingClass.
  	primitive = 117 
  		ifTrue:[selector := ((aClass includesSelector: selector)
  					ifTrue: [aClass compiledMethodAt: selector]
  					ifFalse: [aClass class compiledMethodAt: selector]) literals first at: 2.
  				export := true]
  		ifFalse:[selector := 'prim', aClass name, selector].
  
  !



More information about the Vm-dev mailing list