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

commits at source.squeak.org commits at source.squeak.org
Sat Oct 27 04:52:21 UTC 2018


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

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

Name: VMMaker.oscog-eem.2476
Author: eem
Time: 26 October 2018, 9:51:21.389836 pm
UUID: 5b991009-c072-40d6-b95a-954c68170353
Ancestors: VMMaker.oscog-akg.2475

Slang:
Make directory names in VMMaker work on FileSystem as well as FileDirectory; a first step to being able to generate sources on Pharo.  Eliminate the obsolete machinesDirName.  Remove unnecessary overrides of shouldBeTranslated (the default is ^true).  Make baseTypeForType: answer e.g. 'int *' for the type 'int*', to comnform to the style I use in coerceTo:sim: and Slang type inferrence.

Simulator:
Fix a bug in strlen: with CArrays.

Restore SpurMemoryManager>>memmove:_:_: for performance but implement it better, adapting to whether memory is a DoubleWordArray or a WordArray.

Revise instantiating plugin simulators.  Remove all the hierarchy searching hacks in tryLoadNewPlugin:pluginEntries: & loadNewPlugin: and nuke newFor:, replacing this with simulatorForInterpreterInterface:.  Add a test, StackInterpreterSimulatorTests>>testPluginSimulators, to check that plugin simulators are instantiated as expected.  Consequently implement some unimplemented coercions in SmartSyntaxPluginSimulator, and fix its doesNotUnderstand: method to not cut back plugin arguments twice (in plugins that mix smart syntax and traditional style).

No longer answer nil from SmartSyntaxInterpreterPlugin class>>simulatorClass, making the defailt to simulate, rather than not.  Make initial attempts at simulating the BalloonEnginePlugin (B2DPlugin) using the rewrite engine to automatically generate overrides for methods that use 32-bit arithmetic.

Simplify simulation of the LocalePlugin; LocalePluginSimulator is not needed.

Move evaluateIfFailed: up to InterpreterPlugin; it is generally useful.

Fix simulation of primitiveCompareColors

=============== Diff against VMMaker.oscog-akg.2475 ===============

Item was added:
+ ----- Method: BalloonEngineSimulation>>ensureUpToDateOverrideFor: (in category 'simulation support') -----
+ ensureUpToDateOverrideFor: aSelector
+ 	"Ensure that an override that uses 32-bit integer arithmetic exists for aSelector"
+ 	| source |
+ 	source := self transformedSourceFor: self class superclass >> aSelector.
+ 	(self class sourceCodeAt: aSelector ifAbsent: ['']) ~= source ifTrue:
+ 		[self class compile: source classified: 'generated overrides']!

Item was added:
+ ----- Method: BalloonEngineSimulation>>ensureUpToDateOverrides (in category 'simulation support') -----
+ ensureUpToDateOverrides
+ 	"Ensure that all methods that require int and unsigned int arithmetic are overridden."
+ 	self selectorsForIntMethods do:
+ 		[:selector| self ensureUpToDateOverrideFor: selector]!

Item was changed:
  ----- Method: BalloonEngineSimulation>>initialize (in category 'initialize') -----
  initialize
  	doProfileStats := false.
+ 	bbPluginName := 'BitBltPlugin'.
+ 	self ensureUpToDateOverrides!
- 	bbPluginName := 'BitBltPlugin'!

Item was added:
+ ----- Method: BalloonEngineSimulation>>obj:at: (in category 'accessing objects') -----
+ obj: object at: index
+ 	"Override to correctly map objBuffer access, which has type int *"
+ 	^(objBuffer at: object + index) signedIntFromLong!

Item was added:
+ ----- Method: BalloonEngineSimulation>>obj:at:put: (in category 'accessing objects') -----
+ obj: object at: index put: value
+ 	"Override to correctly map objBuffer access, which has type int *"
+ 	objBuffer at: object + index put: value signedIntToLong!

Item was added:
+ ----- Method: BalloonEngineSimulation>>selectorsForIntMethods (in category 'simulation support') -----
+ selectorsForIntMethods
+ 	"Ensure that all methods that require int and unsigned int arithmetic are overridden."
+ 	| selectors cg |
+ 	selectors := OrderedCollection new.
+ 	cg := CCodeGenerator new.
+ 	^(BalloonEnginePlugin organization listAtCategoryNamed: 'beziers-simple') select:
+ 		[:selector|
+ 		(BalloonEnginePlugin >> selector) pragmas anySatisfy:
+ 			[:p| | type |
+ 			 p keyword == #var:type: ifTrue:
+ 				[type := p arguments last].
+ 			 p keyword == #var:declareC: ifTrue:
+ 				[type := cg
+ 							extractTypeFor: p arguments first
+ 							fromDeclaration: p arguments last].
+ 			 type notNil
+ 			 and: [type last = $* ifTrue:
+ 					[type := cg baseTypeForPointerType: type].
+ 				#(int #'unsigned int') includes: (cg baseTypeForType: type)]]]!

Item was added:
+ ----- Method: BalloonEngineSimulation>>stepToFirstBezierIn:at: (in category 'generated overrides') -----
+ stepToFirstBezierIn: bezier at: yValue
+ 	"Initialize the bezier at yValue.
+ 	TODO: Check if reducing maxSteps from 2*deltaY to deltaY 
+ 		brings a *significant* performance improvement.
+ 		In theory this should make for double step performance
+ 		but will cost in quality. Might be that the AA stuff will
+ 		compensate for this - but I'm not really sure."
+ 
+ 	<inline: false>
+ 	<var: #updateData type: 'int *'>
+ 	| updateData deltaY maxSteps scaledStepSize squaredStepSize startX startY viaX viaY endX endY fwX1 fwX2 fwY1 fwY2 fwDx fwDDx fwDy fwDDy |
+ 	((self isWide: bezier) not and: [ yValue >= (self bezierEndYOf: bezier) ])
+ 		ifTrue: [ ^ self edgeNumLinesOf: bezier put: 0 ].	"Do a quick check if there is anything at all to do"	"Now really initialize bezier"
+ 	startX := self edgeXValueOf: bezier.
+ 	startY := self edgeYValueOf: bezier.
+ 	viaX := self bezierViaXOf: bezier.
+ 	viaY := self bezierViaYOf: bezier.
+ 	endX := self bezierEndXOf: bezier.
+ 	endY := self bezierEndYOf: bezier.
+ 	deltaY := endY - startY.	"Initialize integer forward differencing"
+ 	fwX1 := (viaX - startX) * 2.
+ 	fwX2 := startX + endX - (viaX * 2).
+ 	fwY1 := (viaY - startY) * 2.
+ 	fwY2 := startY + endY - (viaY * 2).
+ 	maxSteps := deltaY * 2.
+ 	maxSteps < 2
+ 		ifTrue: [ maxSteps := 2 ].
+ 	scaledStepSize := 16r1000000 // maxSteps.
+ 	squaredStepSize := self absoluteSquared8Dot24: scaledStepSize.
+ 	fwDx := fwX1 * scaledStepSize.
+ 	fwDDx := fwX2 * squaredStepSize * 2.
+ 	fwDx := fwDx + (fwDDx // 2).
+ 	fwDy := fwY1 * scaledStepSize.
+ 	fwDDy := fwY2 * squaredStepSize * 2.
+ 	fwDy := fwDy + (fwDDy // 2).	"Store the values"
+ 	self edgeNumLinesOf: bezier put: deltaY.
+ 	updateData := self bezierUpdateDataOf: bezier.
+ 	updateData at: GBUpdateX put: (startX * 256) asC_int.
+ 	updateData at: GBUpdateY put: (startY * 256) asC_int.
+ 	updateData at: GBUpdateDX put: fwDx asC_int.
+ 	updateData at: GBUpdateDY put: fwDy asC_int.
+ 	updateData at: GBUpdateDDX put: fwDDx asC_int.
+ 	updateData at: GBUpdateDDY put: fwDDy asC_int.	"And step to the first scan line"
+ 	(startY := self edgeYValueOf: bezier) = yValue
+ 		ifFalse: [ 
+ 			self stepToNextBezierIn: bezier at: yValue.	"Adjust number of lines remaining"
+ 			self edgeNumLinesOf: bezier put: deltaY - (yValue - startY) ]!

Item was added:
+ ----- Method: BalloonEngineSimulation>>stepToNextBezierForward:at: (in category 'generated overrides') -----
+ stepToNextBezierForward: updateData at: yValue
+ 	"Incrementally step to the next scan line in the given bezier update data.
+ 	Note: This method has been written so that inlining works, e.g.,
+ 		not declaring updateData as 'int*' but casting it on every use."
+ 
+ 	<var: #updateData type: 'int *'>
+ 	<inline: true>
+ 	| minY lastX lastY fwDx fwDy |
+ 	lastX := updateData at: GBUpdateX.
+ 	lastY := updateData at: GBUpdateY.
+ 	fwDx := updateData at: GBUpdateDX.
+ 	fwDy := updateData at: GBUpdateDY.
+ 	minY := yValue * 256.	"Step as long as we haven't yet reached minY and also
+ 	as long as fwDy is greater than zero thus stepping down.
+ 	Note: The test for fwDy should not be necessary in theory
+ 		but is a good insurance in practice."
+ 	[ minY > lastY and: [ fwDy >= 0 ] ]
+ 		whileTrue: [ 
+ 			lastX := lastX + (fwDx + 16r8000 signedBitShift: -16).
+ 			lastY := lastY + (fwDy + 16r8000 signedBitShift: -16).
+ 			fwDx := fwDx + (updateData at: GBUpdateDDX).
+ 			fwDy := fwDy + (updateData at: GBUpdateDDY) ].
+ 	updateData at: GBUpdateX put: lastX asC_int.
+ 	updateData at: GBUpdateY put: lastY asC_int.
+ 	updateData at: GBUpdateDX put: fwDx asC_int.
+ 	updateData at: GBUpdateDY put: fwDy asC_int.
+ 	^ lastX signedBitShift: -8!

Item was added:
+ ----- Method: BalloonEngineSimulation>>transformedSourceFor: (in category 'simulation support') -----
+ transformedSourceFor: m
+ 	"Transform all references to #int variables in the source code of m into var asC_int
+ 	 and all references to #'unsigned int' variables into var asC_unsigned_int"
+ 	| tm rules cgen |
+ 	tm := m asTranslationMethodOfClass: TMethod.
+ 	tm recordDeclarationsIn: (cgen := CCodeGenerator new).
+ 	rules := RBParseTreeRewriter new.
+ 	#(#'int *' #'unsigned int *')
+ 		with: #(asC_int asC_unsigned_int)
+ 		do: [:type :coercionMessage|
+ 			(tm declarations keys select: [:v| (tm typeFor: v in: cgen) = type]) do:
+ 				[:var| "make this use ``@expr and editSource breaks"
+ 				rules replace: var, ' at: `@index put: `@expr' with: var, ' at: `@index put: `@expr ', coercionMessage]].
+ 	#(#'int' #'unsigned int')
+ 		with: #(asC_int asC_unsigned_int)
+ 		do: [:type :coercionMessage|
+ 			(tm declarations keys select: [:v| (tm typeFor: v in: cgen) = type]) do:
+ 				[:var|
+ 				rules
+ 					replace: var, ' := `@args' with: var, ' := `@args ', coercionMessage;
+ 					replace: var with: var, ' ', coercionMessage]].
+ 	(rules executeTree: (m methodClass parseTreeFor: m selector)) ifTrue:
+ 		[^rules tree newSource].
+ 	self error: 'parse tree rewrite failed'!

Item was changed:
  ----- Method: BitBltSimulator>>primitive:parameters:receiver: (in category 'simulation') -----
  primitive: primitiveName parameters: parameterTypesArray receiver: rcvrType
+ 	"This exists just to check the set of methods that use smart syntax for which
+ 	 marshallers have been written.  If a case cannot be found you'll have to write
+ 	 a marshaller for the case in question that follows the approach taken in the
+ 	 marshallers below."
+ 	simulator forMap ifTrue:
+ 		[Notification new
+ 			tag: {#forMap. primitiveName. parameterTypesArray. rcvrType};
+ 			signal].
  	primitiveName caseOf: {
+ 		['primitivePixelValueAt']		-> [^self].
+ 		['primitiveCompareColors']	-> [^self] }!
- 		['primitivePixelValueAt'] -> [^self] }!

Item was added:
+ ----- Method: BitBltSimulator>>primitiveCompareColors (in category 'primitives') -----
+ primitiveCompareColors
+ 	"This is a hack to mimic the SmartSyntaxPlugin support for primitive:parameters:receiver:
+ 	 which is hacked here at BitBltSimulator>>primitive:parameters:receiver:"
+ 	"rcvr := self
+ 				primitive: 'primitiveCompareColors'
+ 				parameters: #(#Unsigned #Unsigned #SmallInteger )
+ 				receiver: #Oop."
+ 	| unsignedBlock colorA colorB testID |
+ 	unsignedBlock := simulator ccgLoad: nil expr: nil asUnsignedValueFrom: nil.
+ 	colorA := unsignedBlock value: (interpreterProxy stackValue: 2).
+ 	colorB := unsignedBlock value: (interpreterProxy stackValue: 1).
+ 	testID := interpreterProxy stackIntegerValue: 0.
+ 	interpreterProxy failed ifFalse:
+ 		[self primitiveCompareColorA: colorA to: colorB test: testID]!

Item was changed:
  ----- Method: CArray>>coerceTo:sim: (in category 'converting') -----
  coerceTo: cTypeString sim: interpreterSimulator
  
  	^cTypeString caseOf: {
  		['int']				-> [self ptrAddress].
  		['float *']			-> [self asSingleFloatAccessor].
  		['double *']			-> [self asDoubleFloatAccessor].
  		['sqInt *']			-> [self shallowCopy unitSize: interpreter bytesPerOop; yourself].
  		['unsigned int *']	-> [self shallowCopy unitSize: 4; yourself].
  		['int *']				-> [self shallowCopy unitSize: 4; yourself].
  		['char *']			-> [self shallowCopy unitSize: 1; yourself].
  		['unsigned char *']	-> [self shallowCopy unitSize: 1; yourself].
  		['unsigned']		-> [self ptrAddress].
  		['sqInt']				-> [self ptrAddress].
+ 		['usqInt']			-> [self ptrAddress].
+ 		['sqIntptr_t']		-> [self shallowCopy unitSize: interpreter bytesPerOop; yourself] }!
- 		['usqInt']			-> [self ptrAddress] }!

Item was changed:
  ----- Method: CCodeGenerator>>baseTypeForType: (in category 'utilities') -----
  baseTypeForType: aCType
  	"Reduce various declarations to the most basic type we can determine."
+ 	| type fpIndex closeidx openidx index |
- 	| type fpIndex closeidx openidx |
  	type := aCType.
  	((openidx := type indexOfSubCollection: 'const ') > 0
  	and: [openidx = 1 or: [(type at: openidx) isSeparator]]) ifTrue:
  		[type := type copyReplaceFrom: openidx to: openidx + 5 with: ''].
  	((type beginsWith: 'unsigned') and: [(type includes: $:) and: [type last isDigit]]) ifTrue:
  		[^#usqInt].
  	"collapse e.g. void (*foo(int bar))(void) to void (*)(void)"
  	(fpIndex := type indexOfSubCollection: '(*') > 0 ifTrue:
  		["elide the function arguments after *, if there are any"
  		 type := type copyReplaceFrom: (type indexOf: $( startingAt: fpIndex + 1)
  					to: (type indexOf: $) startingAt: fpIndex + 1)
  					with: ''.
  		 "elide the function name after *, if there is one"
  		 type := type copyReplaceFrom: fpIndex + 2
  					to: (type indexOf: $) startingAt: fpIndex + 1)
  					with: ')'].
  	"collapse [size] to *"
  	openidx := 0.
  	[(openidx := type indexOf: $[ startingAt: openidx + 1) > 0
  	 and: [(closeidx := type indexOf: $] startingAt: openidx + 1) > 0]] whileTrue:
  		[type := type copyReplaceFrom: openidx to: closeidx with: '*'].
+ 	type := type withBlanksTrimmed.
+ 	index := type size.
+ 	"Ensure there is a space between the type and any trailing *'s"
+ 	[(type at: index) == $*] whileTrue:
+ 		[index := index - 1].
+ 	(index < type size
+ 	 and: [(type at: index) ~~ Character space]) ifTrue:
+ 		[type := (type copyFrom: 1 to: index), ' ', (type copyFrom: index + 1 to: type size)].
+ 	^type!
- 	^type withBlanksTrimmed!

Item was changed:
  ----- Method: CoInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr switched |
  	<inline: true>
  
  	methodHeader := self rawHeaderOf: newMethod.
  	self assert: (self isCogMethodReference: methodHeader) not.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: 0. "FoxIFSavedIP"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialIPForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[self reapAndResetErrorCodeTo: localSP header: methodHeader]].
  
+ 	self assert: (self frameNumArgs: localFP) = argumentCount.
- 	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 switched := self handleStackOverflowOrEventAllowContextSwitch:
  						(self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self returnToExecutive: true postContextSwitch: switched.
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: CogVMSimulator>>ioLoadFunction:From: (in category 'plugin support') -----
  ioLoadFunction: functionString From: pluginString
  	"Load and return the requested function from a module"
  	| firstTime plugin fnSymbol |
  	firstTime := false.
  	fnSymbol := functionString asSymbol.
  	transcript
  		cr;
  		show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
  				(pluginString isEmpty ifTrue:['vm'] ifFalse:[pluginString]).
  	(breakSelector notNil
+ 	 and: [(pluginString size = breakSelector size
+ 			and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
+ 		or: [functionString size = breakSelector size
+ 			and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
+ 		[self halt: pluginString, '>>', functionString].
- 	 and: [pluginString size = breakSelector size
- 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0
- 		or: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
- 		[self halt: functionString].
  	plugin := pluginList 
  				detect:[:any| any key = pluginString asString]
  				ifNone:
  					[firstTime := true.
  					self loadNewPlugin: pluginString].
  	plugin ifNil:
  		[firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
  		 ^0].
  	plugin := plugin value.
  	mappedPluginEntries doWithIndex:
  		[:pluginAndName :index|
  		((pluginAndName at: 1) == plugin 
  		and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
  			[^index]].
  	(plugin respondsTo: fnSymbol) ifFalse:
  		[firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
  		 ^0].
  	mappedPluginEntries addLast: (Array
  									with: plugin
  									with: fnSymbol
  									with: [plugin perform: fnSymbol. self]).
+ 	transcript show: ' ... okay'.
- 	"Transcript show: ' ... okay'."
- 	transcript cr.
  	^ mappedPluginEntries size!

Item was changed:
  ----- Method: CogVMSimulator>>ioLoadFunction:From:AccessorDepthInto: (in category 'plugin support') -----
  ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr
  	"Load and return the requested function from a module.
  	 Assign the accessor depth through accessorDepthPtr.
  	 N.B. The actual code lives in platforms/Cross/vm/sqNamedPrims.h"
  	| firstTime plugin fnSymbol |
  	firstTime := false.
  	fnSymbol := functionString asSymbol.
  	transcript
  		cr;
  		show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
  				(pluginString isEmpty ifTrue:['vm'] ifFalse:[pluginString]).
  	(breakSelector notNil
+ 	 and: [(pluginString size = breakSelector size
+ 			and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
+ 		or: [functionString size = breakSelector size
+ 			and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
+ 		[self halt: pluginString, '>>', functionString].
- 	 and: [pluginString size = breakSelector size
- 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0
- 		or: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
- 		[self halt: functionString].
  	plugin := pluginList 
  				detect: [:any| any key = pluginString asString]
  				ifNone:
  					[firstTime := true.
  					 self loadNewPlugin: pluginString].
  	plugin ifNil:
  		[firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
  		 ^0].
  	plugin := plugin value.
  	mappedPluginEntries doWithIndex:
  		[:pluginAndName :index|
  		 ((pluginAndName at: 1) == plugin 
  		  and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
+ 			[firstTime ifTrue: [transcript show: ' ... okay'].
- 			[firstTime ifTrue: [transcript show: ' ... okay'; cr].
  			 accessorDepthPtr at: 0 put: (pluginAndName at: 4).
  			 ^index]].
  	firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
- 	transcript cr.
  	^0!

Item was added:
+ ----- Method: Integer>>asC_int (in category '*VMMaker-interpreter simulator') -----
+ asC_int
+ 	^self >= 0
+ 		ifTrue: [self bitAnd: 16rFFFFFFFF]
+ 		ifFalse: [(self bitAnd: 16rFFFFFFFF) - 16r100000000]!

Item was added:
+ ----- Method: Integer>>asC_unsigned_int (in category '*VMMaker-interpreter simulator') -----
+ asC_unsigned_int
+ 	^self bitAnd: 16rFFFFFFFF!

Item was changed:
  ----- Method: Integer>>coerceTo:sim: (in category '*VMMaker-interpreter simulator') -----
  coerceTo: cTypeString sim: interpreter
  
  	| unitSize |
  	cTypeString last = $* ifTrue:  "C pointer"
  		[unitSize := cTypeString caseOf: {
  		[#'char *'] -> [1].
  		[#'short *'] -> [2].
  		[#'int *'] -> [4].
  		[#'long long *'] -> [8].
  		[#'float *'] -> [^CFloatArray basicNew interpreter: interpreter address: self unitSize: 4; yourself].
  		[#'double *'] -> [^CFloatArray basicNew interpreter: interpreter address: self unitSize: 8; yourself].
  		[#'unsigned *'] -> [4].
  		[#'unsigned int *'] -> [4].
  		[#'unsigned char *'] -> [1].
  		[#'signed char *'] -> [1].
  		[#'unsigned short *'] -> [2].
  		[#'unsigned long long *'] -> [8].
+ 		[#'oop *'] -> [interpreter objectMemory bytesPerOop].
- 		[#'oop *'] -> [interpreter bytesPerOop].
  		}
+ 		otherwise: [interpreter objectMemory wordSize].
- 		otherwise: [interpreter wordSize].
  		^CArray basicNew
  			interpreter: interpreter address: self unitSize: unitSize;
  			yourself].
  	^self  "C number (int, char, float, etc)"!

Item was changed:
  ----- Method: InternetConfigPlugin>>primitiveGetStringKeyedBy: (in category 'system primitives') -----
  primitiveGetStringKeyedBy: aKey
  	| oop ptr size aString keyLength |
  
  	<var: #aString declareC: 'char aString[1025]'>
  	<var: #ptr type: 'char *'>
  	self primitive: 'primitiveGetStringKeyedBy'
  		parameters: #(String).
+ 	self cCode: '' inSmalltalk: [aString := ByteString new: 1025].
- 	
  	keyLength := interpreterProxy byteSizeOf: aKey cPtrAsOop.
  	size := self sqInternetConfigurationGetStringKeyedBy: aKey keySize: keyLength into: aString.
  	oop := interpreterProxy instantiateClass: interpreterProxy classString indexableSize: size.
  	ptr := interpreterProxy firstIndexableField: oop.
  	0 to: size-1 do:[:i|
  		ptr at: i put: (aString at: i)].
  	^oop.
  !

Item was added:
+ ----- Method: InternetConfigPlugin>>sqInternetConfigurationGetStringKeyedBy:keySize:into: (in category 'simulation') -----
+ sqInternetConfigurationGetStringKeyedBy: keyCArray keySize: keySize into: aString
+ 	<doNotGenerate>
+ 	| result |
+ 	result := InternetConfiguration primitiveGetStringKeyedBy: (self asString: keyCArray size: keySize).
+ 	self strncpy: aString _: result _: (aString size min: result size).
+ 	^result size!

Item was removed:
- ----- Method: InterpreterPlugin class>>newFor: (in category 'simulation') -----
- newFor: anUnsimulatedInterpreterPluginClass
- 	"Overridden by SmartSyntaxPluginSimulator to wrap a specific plugin class."
- 	^self new!

Item was added:
+ ----- Method: InterpreterPlugin class>>simulatorForInterpreterInterface: (in category 'simulation') -----
+ simulatorForInterpreterInterface: objectMemoryOrInterpreterProxy
+ 	"Answer an uninitialized (in the sense that the plugin has been sent initialize, but not initialiseModule)
+ 	 simulator for the receiver, or nil, if the receiver answers nil to simulatorClass.  Overridden by
+ 	 SmartSyntaxPluginSimulator to answer an instance of SmartSyntaxPluginSimulator wrapped around
+ 	 an uniniialized simulator for the receiver."
+ 
+ 	^self simulatorClass ifNotNil:
+ 		[:simClass|
+ 		 simClass new
+ 			setInterpreter: objectMemoryOrInterpreterProxy;
+ 			yourself]!

Item was added:
+ ----- Method: InterpreterPlugin>>evaluateIfFailed: (in category 'simulation') -----
+ evaluateIfFailed: aBlock
+ 	"Evaluate aBlock, catching primtiive failure, and failing if so.
+ 	 Answer if evaluating aBlock caused primitive failure."
+ 	<doNotGenerate>
+ 	aBlock
+ 		on: Error
+ 		do: [:ex|
+ 			((ex signalerContext selector beginsWith: #primitiveFailed) "e.g. could be error: sent from primitiveFailed:"
+ 			 or: [ex signalerContext sender selector beginsWith: #primitiveFailed]) ifFalse:
+ 				[ex pass].
+ 			interpreterProxy primitiveFail.
+ 			^true].
+ 	^false!

Item was changed:
  ----- Method: InterpreterSimulator>>loadNewPlugin: (in category 'plugin support') -----
  loadNewPlugin: pluginString
+ 	| plugin plugins realPluginClass |
- 	| plugin plugins simulatorClasses |
  	transcript cr; show: 'Looking for module ', pluginString.
  	"but *why*??"
+ 	plugins := InterpreterPlugin allSubclasses select:
+ 					[:psc|
+ 					 psc moduleName asString = pluginString asString
+ 					 and: [psc shouldBeTranslated]].
+ 	 plugins isEmpty ifTrue: [self transcript show: ' ... not found'. ^nil].
+ 	 plugins size > 1 ifTrue: [^self error: 'This won''t work...'].
+ 	 "plugins size > 1 ifTrue:
+ 		[self transcript show: '...multiple plugin classes; choosing ', plugins last name]."
+ 	 realPluginClass := plugins anyOne. "hopefully lowest in the hierarchy..."
+ 	 plugin := realPluginClass simulatorForInterpreterInterface: self.
+ 	 (plugin respondsTo: #initialiseModule) ifTrue:
- 	(#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: pluginString) ifTrue:
- 		[transcript show: ' ... defeated'. ^nil].
- 	plugins := InterpreterPlugin allSubclasses select: [:psc| psc moduleName asString = pluginString asString].
- 	simulatorClasses := (plugins
- 							select: [:psc| psc simulatorClass notNil]
- 							thenCollect: [:psc| psc simulatorClass]) asSet.
- 	simulatorClasses isEmpty ifTrue: [transcript show: ' ... not found'. ^nil].
- 	simulatorClasses size > 1 ifTrue: [^self error: 'This won''t work...'].
- 	plugins size > 1 ifTrue:
- 		[transcript show: '...multiple plugin classes; choosing ', plugins last name].
- 	plugin := simulatorClasses anyOne newFor: plugins last. "hopefully lowest in the hierarchy..."
- 	plugin setInterpreter: self. "Ignore return value from setInterpreter"
- 	(plugin respondsTo: #initialiseModule) ifTrue:
  		[plugin initialiseModule ifFalse:
+ 			[self transcript show: ' ... initialiser failed'. ^nil]]. "module initialiser failed"
- 			[transcript show: ' ... initialiser failed'. ^nil]]. "module initialiser failed"
  	pluginList := pluginList copyWith: (pluginString asString -> plugin).
  	transcript show: ' ... loaded'.
  	^pluginList last!

Item was removed:
- ----- Method: JPEGReadWriter2Plugin class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^SmartSyntaxPluginSimulator!

Item was removed:
- ----- Method: JPEGReadWriter2Plugin>>evaluateIfFailed: (in category 'simulation') -----
- evaluateIfFailed: aBlock
- 	"Evaluate aBlock, catching primtiive failure, and failing if so.
- 	 Answer if evaluating aBlock caused primitive failure."
- 	<doNotGenerate>
- 	aBlock
- 		on: Error
- 		do: [:ex|
- 			((ex signalerContext selector beginsWith: #primitiveFailed) "e.g. could be error: sent from primitiveFailed:"
- 			 or: [ex signalerContext sender selector beginsWith: #primitiveFailed]) ifFalse:
- 				[ex pass].
- 			interpreterProxy primitiveFail.
- 			^true].
- 	^false!

Item was removed:
- ----- Method: LargeIntegersPlugin class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^SmartSyntaxPluginSimulator!

Item was removed:
- ----- Method: LocalePlugin class>>moduleName (in category 'translation') -----
- moduleName
- 
- 	^ 'LocalePlugin'!

Item was removed:
- ----- Method: LocalePlugin class>>shouldBeTranslated (in category 'translation') -----
- shouldBeTranslated
- 	^true!

Item was removed:
- ----- Method: LocalePlugin class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^LocalePluginSimulator!

Item was added:
+ ----- Method: LocalePlugin>>sqLocGetTimezoneOffset (in category 'simulation support') -----
+ sqLocGetTimezoneOffset
+ 	<doNotGenerate>
+ 	^(DateAndTime localTimeZone offset asSeconds / 60) rounded!

Item was added:
+ ----- Method: LocalePlugin>>sqLocInitialize (in category 'simulation support') -----
+ sqLocInitialize
+ 	<doNotGenerate>
+ 	^true!

Item was removed:
- LocalePlugin subclass: #LocalePluginSimulator
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'VMMaker-Plugins'!

Item was removed:
- ----- Method: LocalePluginSimulator class>>shouldBeTranslated (in category 'translation') -----
- shouldBeTranslated
- 	"This class should not be translated"
- 	^false!

Item was removed:
- ----- Method: LocalePluginSimulator>>primitiveTimezoneOffset (in category 'primitives') -----
- primitiveTimezoneOffset
- 	"return the number of minutes this VM's time value is offset from UTC
- 	For the simulation, use the same timezone as the simulator."
- 
- 	interpreterProxy methodReturnInteger: (DateAndTime localTimeZone offset asSeconds / 60) rounded!

Item was removed:
- ----- Method: LocalePluginSimulator>>sqLocInitialize (in category 'simulation') -----
- sqLocInitialize
- 
- 	^true!

Item was added:
+ ----- Method: NewObjectMemorySimulator>>getStackPointer (in category 'interpreter access') -----
+ getStackPointer
+ 	"hack around the CoInterpreter/ObjectMemory split refactoring"
+ 	^coInterpreter getStackPointer!

Item was changed:
  ----- Method: SmartSyntaxInterpreterPlugin class>>simulatorClass (in category 'simulation') -----
  simulatorClass
+ 	"For running from Smalltalk - answer a class that can be used to simulate the receiver, or nil if you want the primitives in this module to always fail, causing simulation to fall through to the Smalltalk code."
- 	"For running from Smalltalk - answer a class that can be used to simulate the receiver, or nil if you want the primitives in this module to always fail, causing simulation to fall through to the Smalltalk code.
- 	By default SmartSyntaxInterpreterPlugin answers nil because methods in these plugins are intended to be embedded in code that pushes and pops from the stack and therefore cannot be run independently.  This wrapper code is generated when translated to C.  But, unfortunately, this code is missing during simulation.  There was an attempt to simulate this, but only the prologue code (getting arg from the stack) is simulated (see simulatePrologInContext:). The epologue code (popping args and pushing result) is not.  So I am making this nil until this can be fixed.
- 	Also, beware that primitive methods that take no args exactly match their primitive name (faking out InterpreterSimulator>>callExternalPrimitive:).  They should only be called from within wrapper code that simulates the prologue and epilogue.  Primitive method that take args don't have this accidental matching problem since their names contain colons while their primitive names do not. - ajh 8/21/2002"
  
+ 	^SmartSyntaxPluginSimulator!
- 	^ nil!

Item was added:
+ ----- Method: SmartSyntaxInterpreterPlugin class>>simulatorForInterpreterInterface: (in category 'simulation') -----
+ simulatorForInterpreterInterface: objectMemoryOrInterpreterProxy
+ 	"Answer an uninitialized (in the sense that the plugin has been sent initialize, but not initialiseModule)
+ 	 simulator for the receiver, or nil, if the receiver answers nil to simulatorClass.  In this case, answer an
+ 	 instance of SmartSyntaxPluginSimulator wrapped around an uniniialized simulator for the receiver."
+ 
+ 	^self simulatorClass ifNotNil: "Maybe specific, or the general SmartSyntaxPluginSimulator"
+ 		[:simClass| | actualPluginSimClass |
+ 		 actualPluginSimClass := simClass == SmartSyntaxPluginSimulator
+ 									ifTrue: [self subclasses 
+ 											detect: [:sc| sc name endsWith: 'Simulator']
+ 											ifNone: [self]]
+ 									ifFalse: [simClass].
+ 		 SmartSyntaxPluginSimulator new
+ 			actualPlugin: actualPluginSimClass new signatureClass: self;
+ 			setInterpreter: objectMemoryOrInterpreterProxy;
+ 			yourself]!

Item was removed:
- ----- Method: SmartSyntaxPluginSimulator class>>newFor: (in category 'simulation') -----
- newFor: anUnsimulatedInterpreterPluginClass
- 	| simulatorClass |
- 	simulatorClass := anUnsimulatedInterpreterPluginClass subclasses
- 						detect: [:sc| sc name endsWith: 'Simulator']
- 						ifNone: [anUnsimulatedInterpreterPluginClass].
- 	^self new
- 		actualPlugin: simulatorClass new signatureClass: anUnsimulatedInterpreterPluginClass;
- 		yourself!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asFloatValueFrom: (in category 'simulation') -----
  ccgLoad: codeGen expr: exprBlock asFloatValueFrom: stackIndex
+ 	^[:oop| interpreterProxy floatValueOf: oop]!
- 	self shouldBeImplemented!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>ccgLoad:expr:asUnsignedValueFrom: (in category 'simulation') -----
  ccgLoad: codeGen expr: exprBlock asUnsignedValueFrom: stackIndex
+ 	^[:oop|
+ 	  interpreterProxy bytesPerOop = 4
+ 		ifTrue: [interpreterProxy positive32BitValueOf: oop]
+ 		ifFalse: [interpreterProxy positive64BitValueOf: oop]]!
- 	self shouldBeImplemented!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>ccgValBlock: (in category 'simulation') -----
  ccgValBlock: aString 
  	^aString caseOf: {
  		['isBytes']			-> [	[:oop|
  								 interpreterProxy success: (interpreterProxy isBytes: oop).
  								 oop]].
  		['isWords']			-> [	[:oop|
  								 interpreterProxy success: (interpreterProxy isWords: oop).
  								 oop]].
  		['isWordsOrBytes']	-> [	[:oop|
  								 interpreterProxy success: (interpreterProxy isWordsOrBytes: oop).
+ 								 oop]].
+ 		['isIndexable']	-> [	[:oop|
+ 								 interpreterProxy success: (interpreterProxy isIndexable: oop).
  								 oop]] }!

Item was changed:
  ----- Method: SmartSyntaxPluginSimulator>>doesNotUnderstand: (in category 'message forwarding') -----
  doesNotUnderstand: aMessage
+ 	| signature selector parameters result sp |
- 	| signature selector parameters result |
  	signature := signatureMap
  					at: aMessage selector
  					ifAbsent: [^super doesNotUnderstand: aMessage].
  	self log: [interpreterProxy coInterpreter printExternalHeadFrame; print: aMessage selector; cr].
+ 	"record the stack pointer to avoid cutting back the stack twice in plugins that mix smart syntax and traditional style."
+ 	sp := interpreterProxy getStackPointer.
  	selector := signature first.
  	parameters := signature second.
  	signature third "receiver block" value: (interpreterProxy stackValue: parameters size).
  	interpreterProxy failed ifTrue:
  		[self log: 'failed in marshalling'.
  		 ^nil].
  	result := [actualPlugin
  					perform: selector
  					withArguments: (parameters withIndexCollect:
  										[:block :index|
  										block value: (interpreterProxy stackValue: parameters size - index)])]
  					on: Notification
  					do: [:ex|
  						ex tag == #getInterpreter ifTrue: [ex resume: interpreterProxy] ifFalse:
  						[ex tag == #getSimulator ifTrue: [ex resume: self]
  							ifFalse: [ex pass]]].
  	interpreterProxy failed ifTrue:
  		[self log: 'failed in execution'.
  		 ^nil].
  	result == actualPlugin ifTrue:
  		[self log: '^self'.
+ 		 "For methods in BitBltSimulator that do their own marshalling, don't double pop"
+ 		 sp = interpreterProxy getStackPointer ifTrue:
+ 			[interpreterProxy pop: interpreterProxy methodArgumentCount].
- 		 interpreterProxy pop: interpreterProxy methodArgumentCount.
  		 ^nil].
  	self log: [interpreterProxy coInterpreter print: '^'; shortPrintOop: result; flush].
+ 	"For methods in BitBltSimulator that do their own marshalling, don't double pop"
+ 	sp = interpreterProxy getStackPointer ifTrue:
+ 		[interpreterProxy
+ 			pop: interpreterProxy methodArgumentCount + 1
+ 			thenPush: result].
- 	interpreterProxy
- 		pop: interpreterProxy methodArgumentCount + 1
- 		thenPush: result.
  	^nil "SmartSyntaxPluginPrimitives return null"!

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

Item was removed:
- ----- Method: SocketPlugin class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^SmartSyntaxPluginSimulator!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>memmove:_:_: (in category 'simulation only') -----
- memmove: destAddress _: sourceAddress _: bytes
- 	<doNotGenerate>
- 	| dst src  |
- 	dst := destAddress asInteger.
- 	src := sourceAddress asInteger.
- 	"Emulate the c library memmove function"
- 	self assert: bytes \\ 4 = 0.
- 	destAddress > sourceAddress
- 		ifTrue:
- 			[bytes - 4 to: 0 by: -4 do:
- 				[:i| self long32At: dst + i put: (self long32At: src + i)]]
- 		ifFalse:
- 			[0 to: bytes - 4 by: 4 do:
- 				[:i| self long32At: dst + i put: (self long32At: src + i)]]!

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

Item was added:
+ ----- Method: SpurMemoryManager>>memcpy:_:_: (in category 'simulation') -----
+ memcpy: destAddress _: sourceAddress _: bytes
+ 	"For SpurGenerationScavenger>>copyToFutureSpace:bytes:. N.B. If ranges overlap, must use memmove."
+ 	<doNotGenerate>
+ 	self deny: ((destAddress <= sourceAddress and: [destAddress asInteger + bytes > sourceAddress])
+ 				or: [sourceAddress <= destAddress and: [sourceAddress asInteger + bytes > destAddress]]).
+ 	^self memmove: destAddress _: sourceAddress _: bytes!

Item was added:
+ ----- Method: SpurMemoryManager>>memmove:_:_: (in category 'simulation') -----
+ memmove: destAddress _: sourceAddress _: bytes
+ 	"Emulate the c library memmove function"
+ 	<doNotGenerate>
+ 	| dst src  |
+ 	dst := destAddress asInteger.
+ 	src := sourceAddress asInteger.
+ 	self assert: bytes \\ 8 + (dst \\ 8) + (src \\ 8) = 0.
+ 	memory bytesPerElement = 8
+ 		ifTrue:
+ 			[destAddress > sourceAddress
+ 				ifTrue:
+ 					[bytes - 8 to: 0 by: -8 do:
+ 						[:i| self long64At: dst + i put: (self long64At: src + i)]]
+ 				ifFalse:
+ 					[0 to: bytes - 8 by: 8 do:
+ 						[:i| self long64At: dst + i put: (self long64At: src + i)]]]
+ 		ifFalse:
+ 			[destAddress > sourceAddress
+ 				ifTrue:
+ 					[bytes - 4 to: 0 by: -4 do:
+ 						[:i| self long32At: dst + i put: (self long32At: src + i)]]
+ 				ifFalse:
+ 					[0 to: bytes - 4 by: 4 do:
+ 						[:i| self long32At: dst + i put: (self long32At: src + i)]]]!

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

Item was changed:
  ----- Method: StackInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
  checkForAndFollowForwardedPrimitiveState
  	"In Spur a primitive may fail due to encountering a forwarder. On failure,
  	 check the accessorDepth for the primitive and if non-negative scan the
  	 args to the depth, following any forwarders.  Answer if any are found so
  	 the prim can be retried.  The primitive index is derived from newMethod."
  	<option: #SpurObjectMemory>
  	| primIndex accessorDepth found scannedStackFrame |
  	self assert: self failed.
  	found := scannedStackFrame := false.
  	primIndex := self primitiveIndexOf: newMethod.
  	self assert: (argumentCount = (self argumentCountOf: newMethod) or: [self isMetaPrimitiveIndex: primIndex]).
  	"If the primitive is one of the meta primitives PrimNumberDoPrimitive or
  	 PrimNumberDoExternalCall, then metaAccessorDepth will have been set
  	 to nil at the start of the primitive, and to the accessor depth of the called
  	 primitive (or external call) immediately before dispatch.  Hence if primIndex
  	 is that of a meta primiitve then if metaAccessorDepth is -2, the accessor
  	 depth is that of the meta primitive, and if > -2, then metaAccessorDepth is
  	 the accessor depth of the primitive (or external call).  SImilarly, if the
  	 primitive is primitiveExternalCall then the accessor depth is that of
  	 primitiveExternalCall until primitiveFunctionPointer is assigned, at which
  	 point the accessor depth is taken from the slot in newMethod's first literal."
  	accessorDepth := ((self isMetaPrimitiveIndex: primIndex)
  						 and: [metaAccessorDepth > -2])
  							ifTrue: [metaAccessorDepth]
  							ifFalse:
  								[(primIndex = PrimNumberExternalCall
  								  and: [primitiveFunctionPointer ~~ #primitiveExternalCall])
  									ifTrue: [self primitiveAccessorDepthForExternalPrimitiveMethod: newMethod]
  									ifFalse: [primitiveAccessorDepthTable at: primIndex]].
  	self assert: (self saneFunctionPointerForFailureOfPrimIndex: primIndex).
+ 	self assert: (accessorDepth between: -1 and: 5).
- 	self assert: (accessorDepth between: -1 and: 4).
  	accessorDepth >= 0 ifTrue:
  		[0 to: argumentCount do:
  			[:index| | oop |
  			oop := self stackValue: index.
  			(objectMemory isNonImmediate: oop) ifTrue:
  				[(objectMemory isForwarded: oop) ifTrue:
  					[self assert: index < argumentCount. "receiver should have been caught at send time."
  					 found := true.
  					 oop := objectMemory followForwarded: oop.
  					 self stackValue: index put: oop.
  					 scannedStackFrame ifFalse:
  						[scannedStackFrame := true.
  						 self
  							followForwardedFrameContents: framePointer
  							stackPointer: stackPointer + (argumentCount + 1 * objectMemory wordSize) "don't repeat effort"]].
  				(accessorDepth > 0
  			 	 and: [(objectMemory hasPointerFields: oop)
  				 and: [objectMemory followForwardedObjectFields: oop toDepth: accessorDepth]]) ifTrue:
  					[found := true]]]].
  	^found!

Item was changed:
  ----- Method: StackInterpreter>>getStackPointer (in category 'primitive support') -----
  getStackPointer
  	"For Alien FFI"
  	<api>
  	<returnTypeC: #'sqInt *'>
+ 	^self cCoerceSimple: stackPointer to: #'sqInt *'!
- 	^self cCoerce: stackPointer to: #'sqInt *'!

Item was changed:
  ----- Method: StackInterpreter>>internalActivateNewMethod (in category 'message sending') -----
  internalActivateNewMethod
  	| methodHeader numTemps rcvr |
  	<inline: true>
  
  	methodHeader := objectMemory methodHeaderOf: newMethod.
  	numTemps := self temporaryCountOfMethodHeader: methodHeader.
  	self assert: argumentCount = (self argumentCountOfMethodHeader: methodHeader).
  	rcvr := self internalStackValue: argumentCount. "could new rcvr be set at point of send?"
  	self assert: (objectMemory isOopForwarded: rcvr) not.
  
  	self internalPush: localIP.
  	self internalPush: localFP.
  	localFP := localSP.
  	self internalPush: newMethod.
  	self setMethod: newMethod methodHeader: methodHeader.
  	self internalPush: (self
  						encodeFrameFieldHasContext: false
  						isBlock: false
  						numArgs: (self argumentCountOfMethodHeader: methodHeader)).
  	self internalPush: objectMemory nilObject. "FxThisContext field"
  	self internalPush: rcvr.
  
  	"Initialize temps..."
  	argumentCount + 1 to: numTemps do:
  		[:i | self internalPush: objectMemory nilObject].
  
  	"-1 to account for pre-increment in fetchNextBytecode"
  	localIP := self pointerForOop: (self initialIPForHeader: methodHeader method: newMethod) - 1.
  
  	(self methodHeaderHasPrimitive: methodHeader) ifTrue:
  		["Skip the CallPrimitive bytecode, if it's there, and store the error code if the method starts
  		  with a long store temp.  Strictly no need to skip the store because it's effectively a noop."
  		 localIP := localIP + (self sizeOfCallPrimitiveBytecode: methodHeader).
  		 primFailCode ~= 0 ifTrue:
  			[self reapAndResetErrorCodeTo: localSP header: methodHeader]].
  
+ 	self assert: (self frameNumArgs: localFP) = argumentCount.
- 	self assert: (self frameNumArgs: localFP) == argumentCount.
  	self assert: (self frameIsBlockActivation: localFP) not.
  	self assert: (self frameHasContext: localFP) not.
  
  	"Now check for stack overflow or an event (interrupt, must scavenge, etc)."
  	localSP < stackLimit ifTrue:
  		[self externalizeIPandSP.
  		 self handleStackOverflowOrEventAllowContextSwitch: (self canContextSwitchIfActivating: newMethod header: methodHeader).
  		 self internalizeIPandSP]!

Item was changed:
  ----- Method: StackInterpreter>>tryLoadNewPlugin:pluginEntries: (in category 'primitive support') -----
  tryLoadNewPlugin: pluginString pluginEntries: pluginEntries
  	"Load the plugin and if on Spur, populate pluginEntries with the prmitives in the plugin."
  	<doNotGenerate>
+ 	| plugin realPluginClass plugins |
- 	| plugin realPluginClass plugins simulatorClasses |
  	self transcript cr; show: 'Looking for module ', pluginString.
  	pluginString isEmpty
  		ifTrue:
  			[plugin := self]
  		ifFalse:
+ 			[plugins := InterpreterPlugin allSubclasses select:
+ 							[:psc|
+ 							 psc moduleName asString = pluginString asString
+ 							 and: [psc shouldBeTranslated]].
+ 			 plugins isEmpty ifTrue: [self transcript show: ' ... not found'. ^nil].
+ 			 plugins size > 1 ifTrue: [^self error: 'This won''t work...'].
+ 			 "plugins size > 1 ifTrue:
+ 				[self transcript show: '...multiple plugin classes; choosing ', plugins last name]."
+ 			 realPluginClass := plugins anyOne. "hopefully lowest in the hierarchy..."
+ 			 plugin := realPluginClass simulatorForInterpreterInterface: objectMemory.
+ 			 (plugin respondsTo: #initialiseModule) ifTrue:
- 			[plugins := InterpreterPlugin allSubclasses select: [:psc| psc moduleName asString = pluginString asString].
- 			simulatorClasses := (plugins
- 									select: [:psc| psc simulatorClass notNil]
- 									thenCollect: [:psc| psc simulatorClass]) asSet.
- 			simulatorClasses isEmpty ifTrue: [self transcript show: ' ... not found'. ^nil].
- 			simulatorClasses size > 1 ifTrue: [^self error: 'This won''t work...'].
- 			(plugins copyWithoutAll: simulatorClasses) notEmpty ifTrue:
- 				[plugins := plugins copyWithoutAll: simulatorClasses].
- 			plugins size > 1 ifTrue:
- 				[self transcript show: '...multiple plugin classes; choosing ', plugins last name].
- 			realPluginClass := plugins last. "hopefully lowest in the hierarchy..."
- 			plugin := simulatorClasses anyOne newFor: realPluginClass.
- 			plugin setInterpreter: objectMemory. "Ignore return value from setInterpreter"
- 			(plugin respondsTo: #initialiseModule) ifTrue:
  				[plugin initialiseModule ifFalse:
  					[self transcript show: ' ... initialiser failed'. ^nil]]]. "module initialiser failed"
  	self transcript show: ' ... loaded'.
  	objectMemory hasSpurMemoryManagerAPI ifTrue:
  		[| realPlugin cg |
  		 self transcript show: '...computing accessor depths'.
  		 plugin class isPluginClass
  			ifTrue:
  				[realPlugin := (plugin isSmartSyntaxPluginSimulator
  									ifTrue: [realPluginClass]
  									ifFalse: [plugin class])
  								 withAllSuperclasses detect: [:class| class shouldBeTranslated].
  				 cg := realPlugin buildCodeGenerator]
  			ifFalse:
  				[cg := self codeGeneratorToComputeAccessorDepth.
  				 primitiveTable withIndexDo:
  					[:prim :index| | depth |
  					 prim isSymbol ifTrue:
  						[depth := cg accessorDepthForSelector: prim.
  						 self assert: (depth isInteger or: [depth isNil and: [(plugin class whichClassIncludesSelector: prim) isNil]]).
  						 primitiveAccessorDepthTable at: index - 1 put: depth]]].
  		 cg exportedPrimitiveNames do:
  			[:primName| | fnSymbol |
  			 fnSymbol := primName asSymbol.
  			 pluginEntries addLast: {plugin.
  									fnSymbol.
  									[plugin perform: fnSymbol. self].
  									cg accessorDepthForSelector: fnSymbol}].
  		 self transcript show: '...done'].
  	^pluginString asString -> plugin!

Item was changed:
  ----- Method: StackInterpreterSimulator>>getErrorObjectFromPrimFailCode (in category 'debugging traps') -----
  getErrorObjectFromPrimFailCode
+ 	(primFailCode > 1 and: [(#(primitiveNew primitiveNewWithArg primitiveFetchNextMourner primitiveAdoptInstance) includes: primitiveFunctionPointer) not]) ifTrue: [self halt].
- 	(primFailCode > 1 and: [(#(primitiveNew primitiveFetchNextMourner primitiveAdoptInstance) includes: primitiveFunctionPointer) not]) ifTrue: [self halt].
  	^super getErrorObjectFromPrimFailCode!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ioLoadFunction:From: (in category 'plugin support') -----
  ioLoadFunction: functionString From: pluginString
  	"Load and return the requested function from a module"
+ 	| firstTime plugin fnSymbol |
+ 	firstTime := false.
- 	| plugin fnSymbol |
  	fnSymbol := functionString asSymbol.
  	transcript
  		cr;
  		show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
  				(pluginString isEmpty ifTrue:['vm'] ifFalse:[pluginString]).
  	(breakSelector notNil
+ 	 and: [(pluginString size = breakSelector size
+ 			and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
+ 		or: [functionString size = breakSelector size
+ 			and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
+ 		[self halt: pluginString, '>>', functionString].
- 	 and: [pluginString size = breakSelector size
- 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0
- 		or: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
- 		[self halt: functionString].
  	plugin := pluginList 
  				detect:[:any| any key = pluginString asString]
+ 				ifNone:[firstTime := true.
+ 						self loadNewPlugin: pluginString].
+ 	plugin ifNil:[transcript show: 'Failed ... no plugin found'. ^ 0].
- 				ifNone:[self loadNewPlugin: pluginString].
- 	plugin ifNil:[
- 		"Transcript cr; show:'Failed ... no plugin found'." ^ 0].
  	plugin := plugin value.
  	mappedPluginEntries doWithIndex:[:pluginAndName :index|
  		((pluginAndName at: 1) == plugin 
+ 			and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
+ 				[firstTime ifTrue: [transcript show:' ... okay'. ^ index]]].
+ 	(plugin respondsTo: fnSymbol) ifFalse:
+ 		[transcript show:'Failed ... primitive not in plugin'. ^ 0].
- 			and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:[
- 				"Transcript show:' ... okay'." ^ index]].
- 	(plugin respondsTo: fnSymbol) ifFalse:[
- 		"Transcript cr; show:'Failed ... primitive not in plugin'." ^ 0].
  	mappedPluginEntries := mappedPluginEntries copyWith: (Array with: plugin with: fnSymbol).
+ 	transcript show: ' ... okay'.
- 	"Transcript show:' ... okay'."
  	^ mappedPluginEntries size!

Item was changed:
  ----- Method: StackInterpreterSimulator>>ioLoadFunction:From:AccessorDepthInto: (in category 'plugin support') -----
  ioLoadFunction: functionString From: pluginString AccessorDepthInto: accessorDepthPtr
  	"Load and return the requested function from a module.
  	 Assign the accessor depth through accessorDepthPtr.
  	 N.B. The actual code lives in platforms/Cross/vm/sqNamedPrims.h"
  	| firstTime plugin fnSymbol |
  	firstTime := false.
  	fnSymbol := functionString asSymbol.
  	transcript
  		cr;
  		show: '(', byteCount printString, ') Looking for ', functionString, ' in ',
  				(pluginString isEmpty ifTrue:['vm'] ifFalse:[pluginString]).
  	(breakSelector notNil
+ 	 and: [(pluginString size = breakSelector size
+ 			and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0])
+ 		or: [functionString size = breakSelector size
+ 			and: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
+ 		[self halt: pluginString, '>>', functionString].
- 	 and: [pluginString size = breakSelector size
- 	 and: [(self strncmp: pluginString _: breakSelector _: pluginString size) = 0
- 		or: [(self strncmp: functionString _: breakSelector _: functionString size) = 0]]]) ifTrue:
- 		[self halt: functionString].
  	plugin := pluginList 
  				detect: [:any| any key = pluginString asString]
  				ifNone:
  					[firstTime := true.
  					 self loadNewPlugin: pluginString].
  	plugin ifNil:
+ 		[firstTime ifTrue: [transcript show: 'Failed ... primitive not in plugin'].
- 		[firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
  		 ^0].
  	plugin := plugin value.
  	mappedPluginEntries doWithIndex:
  		[:pluginAndName :index|
  		 ((pluginAndName at: 1) == plugin 
  		  and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
+ 			[firstTime ifTrue: [transcript show: ' ... okay'].
- 			[firstTime ifTrue: [transcript show: ' ... okay'; cr].
  			 accessorDepthPtr at: 0 put: (pluginAndName at: 4).
  			 ^index]].
+ 	firstTime ifTrue: [transcript show: 'Failed ... primitive not in plugin'].
- 	firstTime ifTrue: [transcript cr; show: 'Failed ... primitive not in plugin'].
- 	transcript cr.
  	^0!

Item was added:
+ ----- Method: StackInterpreterSimulatorTests>>testPluginSimulators (in category 'tests') -----
+ testPluginSimulators
+ 	"Test that every plugin under InterpreterPlugin that shouldBeTranslated can also instantiate a simulator.
+ 	 Test that every SmartSyntaxInterpreterPlugin is simulated via a SmartSyntaxPluginSimulator."
+ 
+ 	| simulatablePlugins objectMemory vm |
+ 	vm := StackInterpreterSimulator newWithOptions: #(ObjectMemory Spur32BitMemoryManager).
+ 	objectMemory := vm objectMemory.
+ 
+ 
+ 	simulatablePlugins := InterpreterPlugin allSubclasses select:
+ 								[:pc| pc shouldBeTranslated and: [pc simulatorClass notNil]].
+ 	simulatablePlugins do:
+ 		[:pc|
+ 		self shouldnt: [self assert: (pc simulatorForInterpreterInterface: objectMemory) notNil]
+ 			raise: Error].
+ 	
+ 	simulatablePlugins := SmartSyntaxInterpreterPlugin allSubclasses select:
+ 								[:pc| pc shouldBeTranslated and: [pc simulatorClass notNil]].
+ 	simulatablePlugins do:
+ 		[:pc|
+ 		self shouldnt:
+ 				[| simulator |
+ 				 simulator := pc simulatorForInterpreterInterface: objectMemory.
+ 				 self assert: simulator class == SmartSyntaxPluginSimulator.
+ 				 pc simulatorClass ifNotNil:
+ 					[:simulatorClass|
+ 					 simulatorClass == SmartSyntaxPluginSimulator
+ 						ifTrue: [self assert: (simulator actualPlugin isKindOf: pc)]
+ 						ifFalse: [self assert: simulator actualPlugin class == simulatorClass]]]
+ 			raise: Error]
+ 	!

Item was changed:
+ ----- Method: TestOSAPlugin class>>declareCVarsIn: (in category 'translation') -----
- ----- Method: TestOSAPlugin class>>declareCVarsIn: (in category 'as yet unclassified') -----
  declareCVarsIn: cg
  	cg addHeaderFile: '<Carbon/Carbon.h>'.
  !

Item was added:
+ ----- Method: TestOSAPlugin class>>simulatorClass (in category 'simulation') -----
+ simulatorClass
+ 	"As yet this can't be simulated because a DescType parameter can't be handled."
+ 	^nil!

Item was changed:
  InterpreterPlugin subclass: #ThreadedFFIPlugin
+ 	instanceVariableNames: 'ffiLogEnabled externalFunctionInstSize ffiLastError allocationMap'
- 	instanceVariableNames: 'ffiLogEnabled externalFunctionInstSize ffiLastError'
  	classVariableNames: 'DefaultMaxStackSize ExternalFunctionAddressIndex ExternalFunctionArgTypesIndex ExternalFunctionFlagsIndex ExternalFunctionStackSizeIndex MaxNumArgs'
  	poolDictionaries: 'FFIConstants'
  	category: 'VMMaker-Plugins-FFI'!
  
  !ThreadedFFIPlugin commentStamp: 'eem 7/21/2011 11:38' prior: 0!
  This plugin provides access to foreign function interfaces on those platforms that provide such. For example Windows DLLs and unix .so's.  This version is designed to support reentrancy and threading, and so uses alloca to stack allocate all memory needed for a given callout.  Specific platforms are implemented by concrete subclasses.  Threaded calls can only be provided within the context of the threaded VM; othewise calls must be blocking.  So code specific to threading is guarded with a
  	self cppIf: COGMTVM
  		ifTrue: [...]
  form to arrange that it is only compiled in the threaded VM context.!

Item was changed:
  ----- Method: ThreadedFFIPlugin class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: cg
  	super declareCVarsIn: cg.
+ 	cg removeConstant: #COGMTVM. "this should be defined at compile time"
+ 	cg removeVariable: #allocationMap "this is simulation only"!
- 	cg removeConstant: #COGMTVM "this should be defined at compile time"!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiAlloc: (in category 'primitive support') -----
  ffiAlloc: bytes
  	"Default to malloc/free.  If a platform needs a different allocator define
  	 something in the preamble and redefine this to take account of that."
  	<cmacro: '(bytes) (usqInt)malloc(bytes)'>
+ 	"Simulate external allocation.  This would be straight-forward were it not for simulating a
+ 	 32-bit system above a 64-bit system, where the result of an allocation won't fit in a 32-bit
+ 	 pointer.  So in this case maintain a map from external allocations to fake addresses."
+ 	| externalAllocation key |
+ 	(self evaluateIfFailed: [externalAllocation := ExternalAddress allocate: bytes]) ifTrue: [^0].
+ 	(self sizeof: #sqIntptr_t) >= Smalltalk wordSize ifTrue:
+ 		[^externalAllocation asInteger].
+ 	allocationMap ifNil:
+ 		[allocationMap := Dictionary new].
+ 	allocationMap at: (key := allocationMap size * (4 * 1024 * 1024) + 16r8E000000) put: externalAllocation asInteger.
+ 	^key!
- 	^ByteArray new: bytes!

Item was removed:
- ----- Method: UUIDPlugin class>>simulatorClass (in category 'simulation') -----
- simulatorClass
- 	^SmartSyntaxPluginSimulator!

Item was changed:
  ----- Method: VMClass>>strlen: (in category 'C library simulation') -----
  strlen: aCString
  	"Simulate strlen(3)"
  	<doNotGenerate>
  	| len |
  
  	aCString isCArray ifTrue:
+ 		[len := 0.
+ 		 [(aCString at: len) = 0 ifTrue: [^len].
+ 		 len := len + 1] repeat]
- 		["CArrays may be 0 terminated or the correct length (in the simulator)"
- 		len := 0.
- 		[(len = aCString size or: [(aCString at: len) = 0]) ifTrue: [^len].
- 		len := len + 1] repeat]
  	ifFalse:
  		[aCString isString ifTrue: 
  			[^aCString size]
  		ifFalse:
  			[aCString class == ByteArray ifTrue: [
  				"ByteArrays may be 0 terminated or the correct length (in the simulator)"
  				len := 0.
  				[(len = aCString size or: [(aCString at: len+1) = 0]) ifTrue: [^len].
  				len := len + 1] repeat]]].
  	"Must be an address"
  	len := 0.
  	[(self byteAt: aCString + len) = 0 ifTrue: [^len].
  	len := len + 1] repeat!

Item was changed:
+ ----- Method: VMMaker class>>forceNewFileNamed: (in category 'file utilities') -----
- ----- Method: VMMaker class>>forceNewFileNamed: (in category 'utilities') -----
  forceNewFileNamed: aFilename
  	"Always output files in unix lf format.
  		A single format is friendlier to e.g. external version control systems.
  		The Microsoft and old MacOS classic C compilers all accept lf format files."
  
  	^(MultiByteFileStream forceNewFileNamed: aFilename)
  		lineEndConvention: #lf;
  		yourself!

Item was added:
+ ----- Method: VMMaker class>>fullNameForPath: (in category 'file utilities') -----
+ fullNameForPath: aPathString
+ 	^(Smalltalk classNamed: #FileReference)
+ 		ifNotNil: [:cfs| aPathString asFileReference asAbsolute fullName]
+ 		ifNil: [FileDirectory default pathFromURI: aPathString]!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCog64VM (in category 'configurations') -----
  generateNewspeakSpurCog64VM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true)
+ 		to: self sourceTree, '/nsspur64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspur64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurCogVM (in category 'configurations') -----
  generateNewspeakSpurCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(	ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true)
+ 		to: self sourceTree, '/nsspursrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspursrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()
  !

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStack64VM (in category 'configurations') -----
  generateNewspeakSpurStack64VM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #( ObjectMemory Spur64BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false)
+ 		to: self sourceTree, '/nsspurstack64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspurstack64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateNewspeakSpurStackVM (in category 'configurations') -----
  generateNewspeakSpurStackVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(	ObjectMemory Spur32BitMemoryManager
  				MULTIPLEBYTECODESETS true
  				NewspeakVM true
  				FailImbalancedPrimitives false)
+ 		to: self sourceTree, '/nsspurstacksrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/nsspurstacksrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakCogVMWithInterpreterClass:options: (in category 'confs-support') -----
  generateSqueakCogVMWithInterpreterClass: interpreterClass options: optionsArray
  	^VMMaker
  		generate: interpreterClass
  		and: StackToRegisterMappingCogit
  		with: optionsArray
+ 		to: self sourceTree, '/src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCog64MTVM (in category 'configurations') -----
  generateSqueakSpurCog64MTVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreterMT
  		and: StackToRegisterMappingCogit
  		with: #(COGMTVM true
  				ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spur64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spur64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCog64VM (in category 'configurations') -----
  generateSqueakSpurCog64VM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spur64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spur64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogMTVM (in category 'configurations') -----
  generateSqueakSpurCogMTVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreterMT
  		and: StackToRegisterMappingCogit
  		with: #(COGMTVM true
  				ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spursrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spursrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSista64VM (in category 'configurations') -----
  generateSqueakSpurCogSista64VM
  	^VMMaker
  		generate: CoInterpreter
  		and: SistaCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur64BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spursista64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spursista64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogSistaVM (in category 'configurations') -----
  generateSqueakSpurCogSistaVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: SistaCogit
  		with: #(	SistaVM true
  				ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spursistasrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spursistasrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurCogVM (in category 'configurations') -----
  generateSqueakSpurCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(ObjectMemory Spur32BitCoMemoryManager
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spursrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spursrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurLowcodeCog64VM (in category 'configurations') -----
  generateSqueakSpurLowcodeCog64VM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(ObjectMemory Spur64BitCoMemoryManager
  				SistaVM true
+ 				LowcodeVM true
-         			LowcodeVM true
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurlowcode64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurlowcode64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurLowcodeCogVM (in category 'configurations') -----
  generateSqueakSpurLowcodeCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: StackToRegisterMappingCogit
  		with: #(ObjectMemory Spur32BitCoMemoryManager
  				SistaVM true
+ 				LowcodeVM true
-         			LowcodeVM true
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurlowcodesrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurlowcodesrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurLowcodeStack64VM (in category 'configurations') -----
  generateSqueakSpurLowcodeStack64VM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(ObjectMemory Spur64BitMemoryManager
  				SistaVM true
+ 				LowcodeVM true
-         			LowcodeVM true
  				FailImbalancedPrimitives false
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurlowcodestack64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurlowcodestack64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurLowcodeStackVM (in category 'configurations') -----
  generateSqueakSpurLowcodeStackVM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(ObjectMemory Spur32BitMemoryManager
  				SistaVM true
+ 				LowcodeVM true
-         			LowcodeVM true
  				FailImbalancedPrimitives false
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurlowcodestacksrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurlowcodestacksrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurRegisterCogVM (in category 'configurations') -----
  generateSqueakSpurRegisterCogVM
  	"No primitives since we can use those for the Cog VM"
  	^VMMaker
  		generate: CoInterpreter
  		and: RegisterAllocatingCogit
  		with: #(ObjectMemory Spur32BitCoMemoryManager)
+ 		to: self sourceTree, '/spurregsrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurregsrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurStack64VM (in category 'configurations') -----
  generateSqueakSpurStack64VM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(ObjectMemory Spur64BitMemoryManager
  				FailImbalancedPrimitives false
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurstack64src'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurstack64src')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakSpurStackVM (in category 'configurations') -----
  generateSqueakSpurStackVM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(ObjectMemory Spur32BitMemoryManager
  				FailImbalancedPrimitives false
  				MULTIPLEBYTECODESETS true
  				bytecodeTableInitializer initializeBytecodeTableForSqueakV3PlusClosuresSistaV1Hybrid)
+ 		to: self sourceTree, '/spurstacksrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/spurstacksrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateSqueakStackVM (in category 'configurations') -----
  generateSqueakStackVM
  	"No primitives since we can use those from the Cog VM"
  	^VMMaker
  		generate: StackInterpreter
  		with: #(FailImbalancedPrimitives false)
+ 		to: self sourceTree, '/stacksrc'
+ 		platformDir: self sourceTree, '/platforms'
- 		to: (FileDirectory default pathFromURI: self sourceTree, '/stacksrc')
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including: #()!

Item was changed:
  ----- Method: VMMaker class>>generateVMPlugins (in category 'configurations') -----
  generateVMPlugins
  	^VMMaker
+ 		generatePluginsTo: self sourceTree, '/src'
- 		generatePluginsTo: (FileDirectory default pathFromURI: self sourceTree, '/src')
  		options: #()
+ 		platformDir: self sourceTree, '/platforms'
- 		platformDir: (FileDirectory default pathFromURI: self sourceTree, '/platforms')
  		including:#(	ADPCMCodecPlugin AsynchFilePlugin
  					BalloonEnginePlugin B3DAcceleratorPlugin B3DEnginePlugin BMPReadWriterPlugin BitBltSimulation
  					BochsIA32Plugin BochsX64Plugin
  					CameraPlugin CroquetPlugin DeflatePlugin DropPlugin
  					"Cryptography Plugins:" DESPlugin DSAPlugin MD5Plugin SHA256Plugin
  					"FT2Plugin" FFTPlugin FileCopyPlugin FilePlugin FileAttributesPlugin FloatArrayPlugin FloatMathPlugin
  					GeniePlugin GdbARMPlugin HostWindowPlugin IA32ABIPlugin ImmX11Plugin InternetConfigPlugin
  					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin
  					ScratchPlugin SecurityPlugin SerialPlugin SocketPlugin
  					SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
  					ThreadedFFIPlugin ThreadedARMFFIPlugin ThreadedIA32FFIPlugin ThreadedX64SysVFFIPlugin ThreadedX64Win64FFIPlugin
  					UnicodePlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
  					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin WeDoPlugin
  					XDisplayControlPlugin)!

Item was removed:
- ----- Method: VMMaker class>>machinesDirName (in category 'accessing') -----
- machinesDirName
- 	^DirNames at: #machineType ifAbsent:[SmalltalkImage current platformName]!

Item was changed:
+ ----- Method: VMMaker class>>makerFor:and:with:to:platformDir: (in category 'instance creation') -----
- ----- Method: VMMaker class>>makerFor:and:with:to:platformDir: (in category 'utilities') -----
  makerFor: interpreterClass and: cogitClassOrNil with: optionsPairsArrayArg to: srcDirName platformDir: platDirName
+ 	"Initialize a VMMaker to generate the VM to the given target directory."
+ 	| optionsPairsArray |
- 	"Initialize a VMMaker to generate the VM to the given target directory. Include plugins in pluginList.
- 	Example:
- 		(VMMaker
- 			generate: NewspeakInterpreter
- 			to: (FileDirectory default pathFromURI: 'cogvm/newspeaksrc')
- 			platformDir: (FileDirectory default pathFromURI: 'cogvm/platforms')
- 			including:#(	AsynchFilePlugin FloatArrayPlugin RePlugin B2DPlugin FloatMathPlugin SecurityPlugin
- 						BMPReadWriterPlugin IA32ABI SocketPlugin BitBltPlugin JPEGReadWriter2Plugin SurfacePlugin
- 						DSAPrims JPEGReaderPlugin UUIDPlugin DropPlugin LargeIntegers UnixOSProcessPlugin
- 						FileCopyPlugin Matrix2x3Plugin Win32OSProcessPlugin FilePlugin MiscPrimitivePlugin ZipPlugin))"
- 	| maker optionsPairsArray |
- 	maker := self forPlatform: 'Cross'.
- 	maker sourceDirectoryName: srcDirName.
- 	maker platformRootDirectoryName: platDirName.
- 	maker interpreterClass: interpreterClass.
  	optionsPairsArray := (cogitClassOrNil isNil or: [optionsPairsArrayArg includes: #Cogit])
  							ifTrue: [optionsPairsArrayArg]
  							ifFalse: [optionsPairsArrayArg, { #Cogit. cogitClassOrNil name }].
+ 	^(self forPlatform: 'Cross')
+ 		sourceDirectoryName: (self fullNameForPath: srcDirName);
+ 		platformRootDirectoryName: (self fullNameForPath: platDirName);
+ 		options: optionsPairsArray;
+ 		interpreterClass: interpreterClass;
+ 		yourself!
- 	maker options: optionsPairsArray.
- 	^maker
- !

Item was changed:
+ ----- Method: VMMaker class>>oldFileNamed: (in category 'file utilities') -----
- ----- Method: VMMaker class>>oldFileNamed: (in category 'utilities') -----
  oldFileNamed: aFilename
  	"Always output files in unix lf format.
  		A single format is friendlier to e.g. external version control systems.
  		The Microsoft and old MacOS classic C compilers all accept lf format files."
  
  	^(MultiByteFileStream oldFileNamed: aFilename)
  		lineEndConvention: #lf;
  		yourself!

Item was changed:
+ ----- Method: VMMaker class>>rootDirectory (in category 'file utilities') -----
- ----- Method: VMMaker class>>rootDirectory (in category 'accessing') -----
  rootDirectory
  	^FileDirectory default directoryNamed: self sourceTree!

Item was changed:
  ----- Method: VMMaker>>initialize (in category 'initialize') -----
  initialize
  	logger := Transcript.
  	inline := true.
  	forBrowser := false.
  	internalPlugins := SortedCollection new.
  	externalPlugins := SortedCollection new.
+ 	platformName := 'Cross'.
- 	platformName := self class machinesDirName.
  	is64BitVM := false.
  	interpreterClassName := StackInterpreterPrimitives name.
  	optionsDictionary := Dictionary newFromPairs: {#BytesPerWord. 4}.
  	VMStructType voidStructTypeCache!



More information about the Vm-dev mailing list