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

commits at source.squeak.org commits at source.squeak.org
Thu Jul 3 01:51:32 UTC 2014


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

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

Name: VMMaker.oscog-eem.795
Author: eem
Time: 2 July 2014, 6:48:03.822 pm
UUID: d77a504d-28ea-407a-9df0-097e6dbaaf06
Ancestors: VMMaker.oscog-eem.794

Spur:
Implement forwarder following on primitive failure for side-
ways calls from mahcine code.

Fix LargeIntegersPlugin>>isNormalized: for forwarders, no
longer assuming that if its arg isn't a SmallInteger it must be
a large integer.  Squash an assert fail in lengthOf:format: on
forwarders by using numSlotsOfAny:.

Make sure a forwarder has an accurate slot count, bumping it
to 1 if it was zero.

Simulator:
Fix Spur simulation of SmartSyntaxInterpreterPlugins with no
explicit simulator subclass.

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

Item was changed:
  ----- Method: CoInterpreter>>ceActivateFailingPrimitiveMethod: (in category 'enilopmarts') -----
  ceActivateFailingPrimitiveMethod: aPrimitiveMethod
  	"An external call or FFI primitive has failed.  Build the frame and
  	 activate as appropriate.  Enter either the interpreter or machine
  	 code depending on whether aPrimitiveMethod has been or is still
  	 cogged.  Note that we could always interpret but want the efficiency
  	 of executing machine code if it is available."
  	<api>
  	| methodHeader |
+ 	self assert: primFailCode ~= 0.
  	self assert: newMethod = aPrimitiveMethod.
+ 	"If we're on Spur, check for forwarders and retry,
+ 	 returning if successful the second time around."
+ 	(objectMemory hasSpurMemoryManagerAPI
+ 	 and: [(objectMemory isOopCompiledMethod: newMethod)
+ 	 and: [self checkForAndFollowForwardedPrimitiveState]]) ifTrue:
+ 		[self halt; initPrimCall.
+ 		 self cCode: [self dispatchFunctionPointer: primitiveFunctionPointer]
+ 			inSmalltalk:
+ 				[| evaluable |
+ 				 evaluable := primitiveFunctionPointer isInteger
+ 								ifTrue: [cogit simulatedTrampolines at: primitiveFunctionPointer]
+ 								ifFalse: [primitiveFunctionPointer].
+ 				 evaluable isMessageSend
+ 					ifTrue: [self assert: evaluable receiver == self]
+ 					ifFalse: [self assert: evaluable isBlock].
+ 				 evaluable value].
+ 		 self successful ifTrue:
+ 			[^self]].
  	methodHeader := self rawHeaderOf: aPrimitiveMethod.
  	(self isCogMethodReference: methodHeader)
  		ifTrue: [self activateCoggedNewMethod: false]
  		ifFalse: [self activateNewMethod]!

Item was added:
+ ----- Method: Cogit>>simulatedTrampolines (in category 'initialization') -----
+ simulatedTrampolines
+ 	<doNotGenerate>
+ 	^simulatedTrampolines!

Item was added:
+ ----- Method: InterpreterPlugin>>isSmartSyntaxPluginSimulator (in category 'accessing') -----
+ isSmartSyntaxPluginSimulator
+ 	^false!

Item was changed:
  ----- Method: LargeIntegersPlugin>>isNormalized: (in category 'oop functions') -----
  isNormalized: anInteger 
+ 	| len maxVal minVal sLen class positive |
+ 	(interpreterProxy isIntegerObject: anInteger) ifTrue:
+ 		[^ true].
+ 	class := interpreterProxy fetchClassOf: anInteger.
+ 	(positive := class = interpreterProxy classLargePositiveInteger) ifFalse:
+ 		[class = interpreterProxy classLargeNegativeInteger ifFalse:
+ 			[interpreterProxy primitiveFailFor: PrimErrBadArgument.
+ 			 ^false]].
- 	| len maxVal minVal sLen |
- 	(interpreterProxy isIntegerObject: anInteger)
- 		ifTrue: [^ true].
  	"Check for leading zero of LargeInteger"
  	len := self digitLength: anInteger.
+ 	len = 0 ifTrue:
+ 		[^ false].
+ 	(self unsafeByteOf: anInteger at: len) = 0 ifTrue:
+ 		[^ false].
- 	len = 0
- 		ifTrue: [^ false].
- 	(self unsafeByteOf: anInteger at: len)
- 			= 0
- 		ifTrue: [^ false].
  	"no leading zero, now check if anInteger is in SmallInteger range or not"
  	sLen := 4.
  	"maximal digitLength of aSmallInteger"
+ 	len > sLen ifTrue:
+ 		[^ true].
+ 	len < sLen ifTrue:
+ 		[^ false].
- 	len > sLen
- 		ifTrue: [^ true].
- 	len < sLen
- 		ifTrue: [^ false].
  	"len = sLen"
+ 	positive
- 	(interpreterProxy fetchClassOf: anInteger)
- 			= interpreterProxy classLargePositiveInteger
  		ifTrue: [maxVal := 1073741823. "SmallInteger maxVal"
  				"all bytes of maxVal but the highest one are just FF's"
  				^ (self unsafeByteOf: anInteger at: sLen)
  					> (self cDigitOfCSI: maxVal at: sLen)]
  		ifFalse: [minVal := -1073741824. "SmallInteger minVal"
  				"all bytes of minVal but the highest one are just 00's"
+ 			(self unsafeByteOf: anInteger at: sLen) < (self cDigitOfCSI: minVal at: sLen) ifTrue:
+ 				[^ false].
+ 			"if just one digit differs, then anInteger < minval (the corresponding digit byte is greater!!)
+ 			and therefore a LargeNegativeInteger"
+ 			1
+ 				to: sLen
+ 				do: [:ix |
+ 					(self unsafeByteOf: anInteger at: ix) = (self cDigitOfCSI: minVal at: ix) ifFalse:
+ 						[^ true]]].
- 			(self unsafeByteOf: anInteger at: sLen)
- 					< (self cDigitOfCSI: minVal at: sLen)
- 				ifTrue: [^ false]
- 				ifFalse: ["if just one digit differs, then anInteger < minval (the corresponding digit byte is greater!!)
- 						and therefore a LargeNegativeInteger"
- 					1
- 						to: sLen
- 						do: [:ix | (self unsafeByteOf: anInteger at: ix)
- 									= (self cDigitOfCSI: minVal at: ix)
- 								ifFalse: [^ true]]]].
  	^ false!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| flags jmp jmpSamplePrim retry continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	<var: #jmp type: #'AbstractInstruction *'>
  	<var: #retry type: #'AbstractInstruction *'>
  	<var: #jmpSamplePrim type: #'AbstractInstruction *'>
  	<var: #continuePostSamplePrim type: #'AbstractInstruction *'>
  	<var: #jmpSampleNonPrim type: #'AbstractInstruction *'>
  	<var: #continuePostSampleNonPrim type: #'AbstractInstruction *'>
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	flags := coInterpreter primitivePropertyFlags: primitiveIndex.
  	(flags anyMask: PrimCallDoNotJIT) ifTrue:
  		[^ShouldNotJIT].
   
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		BytesPerWord = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + BytesPerWord R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSampleNonPrim := self JumpNonZero: 0.
  		continuePostSampleNonPrim := self Label].
  
  	"Old full prim trace is in VMMaker-eem.550 and prior"
  	self recordPrimTrace ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	retry := self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayCallBack) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayCallBack) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive"
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayCallBack)
  		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
+ 			["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
+ 			  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
+ 			 self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction).
+ 			 backEnd genSubstituteReturnAddress:
- 			[backEnd genSubstituteReturnAddress:
  				((flags anyMask: PrimCallCollectsProfileSamples)
  					ifTrue: [cePrimReturnEnterCogCodeProfiling]
  					ifFalse: [cePrimReturnEnterCogCode]).
  			 self JumpRT: primitiveRoutine asInteger.
  			 primInvokeLabel := self Label.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
  			self CallRT: primitiveRoutine asInteger.
  			primInvokeLabel := self Label.
  			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				BytesPerWord = 4
  					ifTrue:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self MoveAw: coInterpreter nextProfileTickAddress + BytesPerWord R: ClassReg.
  						 self OrR: TempReg R: ClassReg]
  					ifFalse:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self CmpCq: 0 R: TempReg].
  				"If set, jump to record sample call."
  				jmpSamplePrim := self JumpNonZero: 0.
  				continuePostSamplePrim := self Label].
  			objectRepresentation maybeCompileRetry: retry onPrimitiveFail: primitiveIndex.
  			self maybeCompileAllocFillerCheck.
  			"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
+ 				success:	stackPointer ->	result (was receiver)
- 				success:	stackPointer	->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  				failure:						receiver
  											arg1
  											...
+ 							stackPointer ->	argN
- 							stackPointer	->	argN
  											return pc
  			In either case we can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  			self MoveAw: coInterpreter instructionPointerAddress
  				R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  			backEnd genLoadStackPointers.
  			"Test primitive failure"
  			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  			backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
  			self flag: 'ask concrete code gen if move sets condition codes?'.
  			self CmpCq: 0 R: TempReg.
  			jmp := self JumpNonZero: 0.
  			"Fetch result from stack"
  			self MoveMw: BytesPerWord r: SPReg R: ReceiverResultReg.
  			self flag: 'currently caller pushes result'.
+ 			self RetN: BytesPerWord].	"return to caller, popping receiver"
- 			self RetN: BytesPerWord].
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
  		jmpSamplePrim notNil ifTrue:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags anyMask: PrimCallNeedsNewMethod).
  			self CallRT: (self cCode: [#ceCheckProfileTick asUnsignedLong]
  							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  			"reenter the post-primitive call flow"
  			self Jump: continuePostSamplePrim].
  		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
  		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
  		jmpSampleNonPrim jmpTarget: self Label.
  		self MoveCq: 0 R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallRT: (self cCode: [#ceCheckProfileTick asUnsignedLong]
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
  	jmp notNil ifTrue:
  		["Jump to restore of receiver reg and proceed to frame build for failure."
  		 jmp jmpTarget: self Label.
  		 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  		 self MoveMw: BytesPerWord * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimReturnEnterCogCodeEnilopmart: (in category 'initialization') -----
  genPrimReturnEnterCogCodeEnilopmart: profiling
  	"Generate the substitute return code for an external or FFI primitive call.
  	 On success simply return, extracting numArgs from newMethod.
  	 On primitive failure call ceActivateFailingPrimitiveMethod: newMethod."
  	| jmpSample continuePostSample jmpFail |
  	<var: #jmpSample type: #'AbstractInstruction *'>
  	<var: #continuePostSample type: #'AbstractInstruction *'>
  	<var: #jmpFail type: #'AbstractInstruction *'>
  	opcodeIndex := 0.
  
  	profiling ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick: if so.
  		  N.B. nextProfileTick is 64-bits so 32-bit systems need to test both halves."
  		BytesPerWord = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + BytesPerWord R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSample := self JumpNonZero: 0.
  		continuePostSample := self Label].
  
  	self maybeCompileAllocFillerCheck.
  
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmpFail := self JumpNonZero: 0.
  
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer	->	result (was receiver)
  										arg1
  										...
  										argN
  										return pc
  		failure:							receiver
  										arg1
  										...
  					stackPointer	->	argN
  										return pc
  	We push the instructionPointer to reestablish the return pc in the success case,
  	but leave it to ceActivateFailingPrimitiveMethod: to do so in the failure case."
  
  	backEnd hasLinkRegister
  		ifTrue:
  			[backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.	"Get and restore ret pc"
  			 self RetN: BytesPerWord]											"Return, popping result from stack"
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.	"Get return pc"
  			 backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveR: ClassReg Mw: 0 r: SPReg.								"Restore return pc"
  			 self RetN: 0].														"Return, popping result from stack"
  
  	"Primitive failed.  Invoke C code to build the frame and continue."
  	jmpFail jmpTarget: (self MoveAw: coInterpreter newMethodAddress R: SendNumArgsReg).
  	"Reload sp with CStackPointer; easier than popping args of checkProfileTick."
  	self MoveAw: self cStackPointerAddress R: SPReg.
  	self 
  		compileCallFor: #ceActivateFailingPrimitiveMethod:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: nil
  		saveRegs: false.
  
+ 	"On Spur ceActivateFailingPrimitiveMethod: may retry the primitive and return if successful.
+ 	 So continue by returning to the caller.
+ 	 Switch back to the Smalltalk stack.  Stack should be in this state:
+ 				success:	stackPointer ->	result (was receiver)
+ 											arg1
+ 											...
+ 											argN
+ 											return pc
+ 	 We can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
+ 	self MoveAw: coInterpreter instructionPointerAddress
+ 		R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
+ 	backEnd genLoadStackPointers.
+ 	backEnd hasLinkRegister
+ 		ifTrue:
+ 			[self MoveMw: 0 r: SPReg R: ReceiverResultReg]	"Fetch result from stack"
+ 		ifFalse:
+ 			[self MoveMw: BytesPerWord r: SPReg R: ReceiverResultReg.	"Fetch result from stack"
+ 			 self PushR: ClassReg].											"Restore return pc on CISCs"
+ 	self flag: 'currently caller pushes result'.
+ 	self RetN: BytesPerWord.	"return to caller, popping receiver"
+ 
  	profiling ifTrue:
  		["Call ceCheckProfileTick: to record sample and then continue.  newMethod
  		 should be up-to-date.  Need to save and restore the link reg around this call."
  		 jmpSample jmpTarget: self Label.
  		 backEnd hasLinkRegister ifTrue: [self PushR: LinkReg].
  		 self CallRT: (self cCode: '(unsigned long)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		 backEnd hasLinkRegister ifTrue: [self PopR: LinkReg].
  		 self Jump: continuePostSample]!

Item was added:
+ ----- Method: SmartSyntaxPluginSimulator>>isPluginClass (in category 'simulation') -----
+ isPluginClass
+ 	"This stands in for SmartSyntaxInterpreterPlugin classes during simulation."
+ 	^true!

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

Item was changed:
  ----- Method: SpurMemoryManager>>forward:to: (in category 'become implementation') -----
  forward: obj1 to: obj2
  	self set: obj1 classIndexTo: self isForwardedObjectClassIndexPun formatTo: self forwardedFormat.
+ 	self storePointer: 0 ofForwarder: obj1 withValue: obj2.
+ 	"For safety make sure the forwarder has a slot count that includes its contents."
+ 	(self rawNumSlotsOf: obj1) = 0 ifTrue:
+ 		[self setRawNumSlotsOf: obj1 to: 1]!
- 	self storePointer: 0 ofForwarder: obj1 withValue: obj2!

Item was changed:
  ----- Method: SpurMemoryManager>>lengthOf:format: (in category 'object access') -----
  lengthOf: objOop format: fmt
  	"Answer the number of indexable units in the given object.
  	 For a CompiledMethod, the size of the method header (in bytes)
  	 should be subtracted from the result of this method."
  	| numSlots |
  	<inline: true>
  	<asmLabel: false> 
+ 	numSlots := self numSlotsOfAny: objOop. "don't let forwarders freak us out..."
- 	numSlots := self numSlotsOf: objOop.
  	fmt <= self sixtyFourBitIndexableFormat ifTrue:
  		[^numSlots].
  	fmt >= self firstByteFormat ifTrue: "bytes, including CompiledMethod"
  		[^numSlots << self shiftForWord - (fmt bitAnd: 7)].
  	fmt >= self firstShortFormat ifTrue:
  		[^numSlots << (self shiftForWord - 1) - (fmt bitAnd: 3)].
  	"fmt >= self firstLongFormat"
  	^numSlots << (self shiftForWord - 2) - (fmt bitAnd: 1)!

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 simulatorClasses |
- 	| plugin plugins simulatorClasses |
  	self transcript cr; show: 'Looking for module ', pluginString.
  	"Defeat loading of the FloatArrayPlugin & Matrix2x3Plugin since complications with 32-bit
  	 float support prevent simulation.  If you feel up to tackling this start by implementing
  		cCoerce: value to: cType
  			^cType = 'float'
  				ifTrue: [value asIEEE32BitWord]
  				ifFalse: [value]
  	 in FloatArrayPlugin & Matrix2x3Plugin and then address the issues in the BalloonEnginePlugin.
  	 See http://forum.world.st/Simulating-the-BalloonEnginePlugin-FloatArrayPlugin-amp-Matrix2x3Plugin-primitives-td4734673.html"
  	(#('FloatArrayPlugin' 'Matrix2x3Plugin') includes: pluginString) ifTrue:
  		[self transcript show: ' ... defeated'. ^nil].
  	pluginString isEmpty
  		ifTrue:
  			[plugin := self]
  		ifFalse:
  			[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 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 := simulatorClasses anyOne newFor: plugins last. "hopefully lowest in the hierarchy..."
  			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].
- 				[realPlugin := plugin class withAllSuperclasses detect: [:class| class shouldBeTranslated].
  				 cg := realPlugin buildCodeGeneratorUpTo: realPlugin]
  			ifFalse:
  				[cg := self codeGeneratorToComputeAccessorDepth.
  				 primitiveTable withIndexDo:
  					[:prim :index| | depth |
  					 prim isSymbol ifTrue:
  						[depth := cg accessorDepthForSelector: prim.
  						 self assert: depth isInteger.
  						 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>>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: [(self str: functionString n: breakSelector cmp: functionString size) = 0]) ifTrue:
+ 		[self halt: functionString].
- 	breakSelector ifNotNil:
- 		[(self str: functionString n: breakSelector cmp: 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 select: [:tuple| tuple first = plugin] an OrderedCollection({an UnixOSProcessPlugin . #getModuleName . [closure] in [] in StackInterpreterSimulatorLSB(StackInterpreter)>>tryLoadNewPlugin:pluginEntries: . nil} {an UnixOSProcessPlugin . #setInterpreter . [closure] in [] in StackInterpreterSimulatorLSB(StackInterpreter)>>tryLoadNewPlugin:pluginEntries: . nil})"
  	mappedPluginEntries doWithIndex:
  		[:pluginAndName :index|
  		 ((pluginAndName at: 1) == plugin 
  		  and:[(pluginAndName at: 2) == fnSymbol]) ifTrue:
  			[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!



More information about the Vm-dev mailing list