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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 3 08:02:49 UTC 2021


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

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

Name: VMMaker.oscog-eem.3019
Author: eem
Time: 3 August 2021, 1:02:06.715258 am
UUID: e99c07f6-81f2-4d58-9ff4-943d9e7ef0dc
Ancestors: VMMaker.oscog-tpr.3018

Cog: use symbolic constants for Spur primitive metadata manipulation.
Refactor linkExternalCall:ifFail: into linkExternalCall:errInto: so it doesn't have to be inlined.
Fix mapToBytecodePCIfActivationOfExternalMethod: to asvoid an assert fail for an interpreter frame activation of an external method.
Use faster length accessors (numSlotsOf: numBytesOfBytes:) in a few places.

Reorder teh storing of newMethod and the setting of stack pointers in compileOnStackExternalPrimitive:flags:, as well as making an invariant on VarBase clear.
CroquetPlugin: simulate ioGatherEntropy:_:, along with a hook to supply constant entropy via InitializationOptions.

=============== Diff against VMMaker.oscog-tpr.3018 ===============

Item was changed:
  ----- Method: CoInterpreter class>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	COGVM := true.
  
  	MinBackwardJumpCountForCompile := 40.
  
  	MaxNumArgs := 15.
  	PrimCallNeedsNewMethod := 1.
  	PrimCallNeedsPrimitiveFunction := 2.
  	PrimCallMayEndureCodeCompaction := 4.
  	PrimCallCollectsProfileSamples := 8.
  	PrimCallDoNotJIT := 16.
  	PrimCallIsExternalCall := 32.
  	"CheckAllocationFillerAfterPrimCall := 32. this has never been successfully used in all the years we've had it; nuking it"
  	PrimCallOnSmalltalkStack := 64. "Speed up simple external prims by avoiding stack switch"
  	PrimCallOnSmalltalkStackAlign2x := 128. "Align stack to a 2 x word size boundary, e.g. for MMX instructions etc"
  	FastCPrimitiveUseCABIFlag := 256.
  
  	"Flags for use in export:flags:, shifted to overlap with the PrimCallXXX flags above"
  	FastCPrimitiveFlag := 1.				"a.k.a. PrimCallOnSmalltalkStack"
  	FastCPrimitiveAlignForFloatsFlag := 2.	"a.k.a. PrimCallOnSmalltalkStackAlign2x"
  	FastCPrimitiveUseCABIFlag := 4.		"a.k.a. FastCPrimitiveUseCABIFlag"
  	PrimitiveMetadataFlagsShift := PrimCallOnSmalltalkStack highBit - FastCPrimitiveFlag highBit.
  
+ 	"And to shift away the flags, to compute the accessor depth, use...
+ 	 c.f. NullSpurMetadata in sq.h"
+ 	SpurPrimitiveAccessorDepthShift := 8.
+ 	SpurPrimitiveFlagsMask := 1 << SpurPrimitiveAccessorDepthShift - 1.
+ 
  	"the primitive trace log; a record of the last 256 named/external primitives or significant events invoked."
  	PrimTraceLogSize := 256. "Room for 256 selectors.  Must be 256 because we use a byte to hold the index"
  	TraceBufferSize := 256 * 3. "Room for 256 events"
  	TraceContextSwitch := self objectMemoryClass basicNew integerObjectOf: 1.
  	TraceBlockActivation := self objectMemoryClass basicNew integerObjectOf: 2.
  	TraceBlockCreation := self objectMemoryClass basicNew integerObjectOf: 3.
  	TraceIncrementalGC := self objectMemoryClass basicNew integerObjectOf: 4.
  	TraceFullGC := self objectMemoryClass basicNew integerObjectOf: 5.
  	TraceCodeCompaction := self objectMemoryClass basicNew integerObjectOf: 6.
  	TraceOwnVM := self objectMemoryClass basicNew integerObjectOf: 7.
  	TraceDisownVM := self objectMemoryClass basicNew integerObjectOf: 8.
  	TraceThreadSwitch := self objectMemoryClass basicNew integerObjectOf: 9.
  	TracePreemptDisowningThread := self objectMemoryClass basicNew integerObjectOf: 10.
  	TraceVMCallback := self objectMemoryClass basicNew integerObjectOf: 11.
  	TraceVMCallbackReturn := self objectMemoryClass basicNew integerObjectOf: 12.
  	TraceStackOverflow := self objectMemoryClass basicNew integerObjectOf: 13.
  	TracePrimitiveFailure := self objectMemoryClass basicNew integerObjectOf: 14.
  	TracePrimitiveRetry := self objectMemoryClass basicNew integerObjectOf: 15.
  
  	TraceIsFromMachineCode := 1.
  	TraceIsFromInterpreter := 2.
  	CSCallbackEnter := 3.
  	CSCallbackLeave := 4.
  	CSEnterCriticalSection := 5.
  	CSExitCriticalSection := 6.
  	CSResume := 7.
  	CSSignal := 8.
  	CSSuspend := 9.
  	CSWait := 10.
  	CSYield := 11.
  	CSCheckEvents := 12.
  	CSThreadSchedulingLoop := 13.
  	CSOwnVM := 14.
  	CSThreadBind := 15.
  	CSSwitchIfNeccessary := 16.
  
  	TraceSources := CArrayAccessor on: #('?' 'm' 'i' 'callbackEnter' 'callbackLeave' 'enterCritical' 'exitCritical' 'resume' 'signal'  'suspend' 'wait' 'yield' 'eventcheck' 'threadsched' 'ownVM' 'bindToThread' 'switchIfNecessary').
  
  	"this is simulation only"
  	RumpCStackSize := 4096!

Item was changed:
  ----- Method: CoInterpreter>>accessorDepthForExternalPrimitiveMethod: (in category 'plugin primitive support') -----
  accessorDepthForExternalPrimitiveMethod: methodObj
  	<api>
  	<option: #SpurMemoryManager>
  	| flags lit |
  	self assert: (self isLinkedExternalPrimitive: methodObj).
  	lit := self literal: 0 ofMethod: methodObj.
  	 flags := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
+  	 ^(objectMemory integerValueOf: flags) >>> SpurPrimitiveAccessorDepthShift!
-  	 ^(objectMemory integerValueOf: flags) bitShift: -8!

Item was changed:
  ----- Method: CoInterpreter>>attemptToLinkExternalPrimitive: (in category 'plugin primitive support') -----
  attemptToLinkExternalPrimitive: methodObj
  	| header primIdx firstLiteral targetFunctionIndex |
  	header := objectMemory methodHeaderOf: methodObj.
  	primIdx := self primitiveIndexOfMethod: methodObj header: header.
  	firstLiteral := self literal: 0 ofMethod: methodObj.
  	self assert: (primIdx = PrimNumberExternalCall
  				 and: [(objectMemory literalCountOfMethodHeader: header) > 0
  				 and: [(objectMemory isArray: firstLiteral)
  				 and: [(objectMemory numSlotsOf: firstLiteral) = 4]]]).
  	 targetFunctionIndex := objectMemory fetchPointer: ExternalCallLiteralTargetFunctionIndex ofObject: firstLiteral.
  	 self assert: (objectMemory isIntegerObject: targetFunctionIndex).
  	 (objectMemory integerValueOf: targetFunctionIndex) = 0 ifTrue:
+ 		[self linkExternalCall: firstLiteral errInto: nil].
- 		[self linkExternalCall: firstLiteral ifFail: []].
  	^firstLiteral!

Item was changed:
  ----- Method: CoInterpreter>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'cog jit support') -----
  functionPointerForCompiledMethod: methodObj primitiveIndex: primitiveIndex primitivePropertyFlagsInto: flagsPtr
  	<api>
  	<returnTypeC: 'void (*functionPointerForCompiledMethodprimitiveIndexprimitivePropertyFlagsInto(sqInt methodObj, sqInt primitiveIndex, sqInt *flagsPtr))(void)'>
  	| functionPointer |
  	<var: #functionPointer declareC: #'void (*functionPointer)(void)'>
  	flagsPtr ifNotNil:
  		[flagsPtr at: 0 put: (self primitivePropertyFlags: primitiveIndex)].
  	functionPointer := self functionPointerFor: primitiveIndex inClass: nil.
  	functionPointer == #primitiveCalloutToFFI ifTrue:
  		[^self functionForPrimitiveCallout].
  	functionPointer == #primitiveExternalCall ifTrue:
  		[| lit |
  		 lit := self attemptToLinkExternalPrimitive: methodObj.
  		 "N.B. We only support the FastCPrimitiveFlag on Spur because Spur
  		  will *not* run a GC to satisfy an allocation in a primitive. The V3
  		  ObjectMemory will and hence the depth of stack needed in a V3
  		  primitive is probably too large to safely execute on a stack page."
  		  objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[| flags shiftedMetadataFlags |
  			 flags := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
  		 	 (objectMemory isIntegerObject: flags) ifTrue:
+ 				[shiftedMetadataFlags := ((objectMemory integerValueOf: flags) bitAnd: SpurPrimitiveFlagsMask) bitShift: PrimitiveMetadataFlagsShift.
+ 				 profileSemaphore ~= objectMemory nilObject ifTrue:
+ 					[shiftedMetadataFlags := shiftedMetadataFlags bitOr: PrimCallCollectsProfileSamples].
- 				[shiftedMetadataFlags := ((objectMemory integerValueOf: flags) bitAnd: 16rFF) bitShift: PrimitiveMetadataFlagsShift.
  				 shiftedMetadataFlags ~= 0 ifTrue:
  					[flagsPtr at: 0 put: shiftedMetadataFlags]]].
  		 ^self functionForPrimitiveExternalCall: methodObj].
  	^functionPointer!

Item was changed:
  ----- Method: CoInterpreter>>mapToBytecodePCIfActivationOfExternalMethod: (in category 'plugin primitive support') -----
  mapToBytecodePCIfActivationOfExternalMethod: ctxtObj
  	(self isExternalMethodInPlugin: (objectMemory fetchPointer: MethodIndex ofObject: ctxtObj)) ifTrue:
  		[(self isMarriedOrWidowedContext: ctxtObj) ifTrue:
+ 			[| theFP |
+ 			 (self isWidowedContext: ctxtObj) ifTrue:
+ 				[^self].
+ 			 theFP := self frameOfMarriedContext: ctxtObj.
+ 			 (self isMachineCodeFrame: theFP) ifFalse:
- 			[(self asserta: (self isWidowedContext: ctxtObj)) ifTrue:
  				[^self]].
  		 self ensureContextHasBytecodePC: ctxtObj]!

Item was changed:
  ----- Method: CogVMSimulator>>classNameOf:Is: (in category 'plugin support') -----
  classNameOf: aClass Is: className
  	"Check if aClass' name is className"
  	| name |
+ 	(objectMemory numSlotsOf: aClass) <= classNameIndex ifTrue:
- 	(objectMemory lengthOf: aClass) <= classNameIndex ifTrue:
  		[^false]. "Not a class but maybe behavior" 
  	name := objectMemory fetchPointer: classNameIndex ofObject: aClass.
  	(objectMemory isBytes: name) ifFalse:
  		[^false].
  	^ className = (self stringOf: name)!

Item was added:
+ ----- Method: CroquetPlugin>>ioGatherEntropy:_: (in category 'simulation support') -----
+ ioGatherEntropy: bytes _: length
+ 	<doNotGenerate>
+ 	| entropy |
+ 	(InitializationOptions at: #entropy ifAbsent: nil)
+ 		ifNotNil: [:repeatableEntropy|
+ 			self assert: repeatableEntropy size = length.
+ 			entropy := repeatableEntropy]
+ 		ifNil:
+ 			[entropy := ByteArray new: length.
+ 			(Random gatherEntropyInto: entropy) ifFalse:
+ 				[^false]].
+ 	self memcpy: bytes _: entropy _: length.
+ 	^true!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  	"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)'>
  	| jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
+ 	self deny: (backEnd hasVarBaseRegister
+ 				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
+ 
  	"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 anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize 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 old full prim trace is in VMMaker-eem.550 and prior.
  	 Old simpler full prim trace is in VMMaker-eem.2969 and prior."
  	(coInterpreter recordPrimTraceForMethod: methodObj) ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	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+PrimCallMayEndureCodeCompaction) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayEndureCodeCompaction) 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: PrimCallMayEndureCodeCompaction)
  		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."
  			 objectMemory hasSpurMemoryManagerAPI ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction)].
  			 backEnd
  				genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil;
  				genSubstituteReturnAddress:
  					((flags anyMask: PrimCallCollectsProfileSamples)
  						ifTrue: [cePrimReturnEnterCogCodeProfiling]
  						ifFalse: [cePrimReturnEnterCogCode]).
  			 self JumpFullRT: primitiveRoutine asInteger.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
  			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  			self CallFullRT: primitiveRoutine asInteger.
  			backEnd genRemoveNArgsFromStack: 0.
  			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				objectMemory wordSize = 4
  					ifTrue:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize 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 maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  			"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
  			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: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  				r: SPReg
  				R: ReceiverResultReg.
  			self RetN: objectMemory wordSize].	"return to caller, popping receiver"
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
  		jmpSamplePrim ifNotNil:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags anyMask: PrimCallNeedsNewMethod).
  			self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  							   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 CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
  	jmp ifNotNil:
  		["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: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOnStackExternalPrimitive:flags: (in category 'primitive generators') -----
  compileOnStackExternalPrimitive: primitiveRoutine flags: flags
  	"Compile a fast call of a C primitive using the current stack page, avoiding the stack switch except on failure.
  	 This convention still uses stackPointer and argumentCount to access operands.  Push all operands to the stack,
  	 assign stackPointer, argumentCount, and zero primFailCode.  Make the call (saving a LinkReg if required).
  	 Test for failure and return.  On failure on Spur, if there is an accessor depth, assign framePointer and newMethod,
  	 do the stack switch, call checkForAndFollowForwardedPrimitiveState, and loop back if forwarders are found.
  	 Fall through to frame build."
  	 
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp retry calleeSavedReg |
  	self assert: (objectRepresentation hasSpurMemoryManagerAPI and: [flags anyMask: PrimCallOnSmalltalkStack]).
+ 	self deny: (backEnd hasVarBaseRegister
+ 				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	"Clear the primFailCode and set argumentCount"
  	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.
  	self genExternalizeStackPointerForFastPrimitiveCall.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	retry := self Label.
  	calleeSavedReg := NoReg.
  	(SPReg ~= NativeSPReg
  	 and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
  		[calleeSavedReg := self availableRegisterOrNoneIn: ABICalleeSavedRegisterMask.
  		 self deny: calleeSavedReg = NoReg.
  		 self MoveR: SPReg R: calleeSavedReg].
  	(flags anyMask: PrimCallOnSmalltalkStackAlign2x)
  		ifTrue: [self AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg]
  		ifFalse:
  			[SPReg ~= NativeSPReg ifTrue:
  				[backEnd genLoadNativeSPRegWithAlignedSPReg]].
  	self CallFullRT: primitiveRoutine.
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	calleeSavedReg ~= NoReg ifTrue:
  		[self MoveR: calleeSavedReg R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"At this point the primitive has cut back stackPointer to point to the result.
  	 The original retpc is (argumentCount + 1) words beneath it."
  	self MoveAw: coInterpreter stackPointerAddress R: TempReg.
  	self MoveMw: (methodOrBlockNumArgs + 1 * objectMemory wordSize) negated
  		r: TempReg
  		R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  	self MoveR: TempReg R: SPReg.
  	backEnd hasLinkRegister
  		ifTrue: [self PopR: ReceiverResultReg] "i.e. get result"
  		ifFalse:
  			[self MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				MoveR: ClassReg Mw: 0 r: TempReg]. "i.e. get result and restore retpc"
  	self RetN: 0.
  
  	jmp jmpTarget: self Label.
  	(coInterpreter accessorDepthForExternalPrimitiveMethod: methodObj) >= 0
  		ifTrue:
  			[| skip |
  			 "Given that following primitive state to the accessor depth is recursive, we're asking for
  			  trouble if we run the fixup on the Smalltalk stack page.  Run it on the full C stack instead.
  			 This won't be a performance issue since primitive failure should be very rare."
  			self MoveR: FPReg Aw: coInterpreter framePointerAddress.
  			self MoveCw: primitiveRoutine asInteger R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress.
- 			self genLoadCStackPointersForPrimCall.
  			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.
+ 			self genLoadCStackPointersForPrimCall.
  			self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  								   inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]).
  			backEnd genLoadStackPointersForFastPrimCall: ClassReg.
  			self CmpCq: 0 R: ABIResultReg.
  			skip := self JumpZero: 0.
  			self MoveCq: 0 R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  			self Jump: retry.
  			skip jmpTarget: self Label]
  		ifFalse: "must reload SPReg to undo any alignment change,"
  			[(flags anyMask: PrimCallOnSmalltalkStackAlign2x) ifTrue:
  				[backEnd genLoadStackPointersForFastPrimCall: ClassReg]].
  	"Finally remember to reload ReceiverResultReg if required.  Even if
  	 arguments have been pushed, the prolog sequence assumes it is live."
  	(self register: ReceiverResultReg isInMask: ABICallerSavedRegisterMask) ifTrue:
  		[self MoveMw: (backEnd hasLinkRegister ifTrue: [methodOrBlockNumArgs] ifFalse: [methodOrBlockNumArgs + 1]) * objectMemory wordSize
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!

Item was changed:
  ----- Method: StackInterpreter>>classNameOf:Is: (in category 'plugin primitive support') -----
  classNameOf: aClass Is: className 
  	"Check if aClass's name is className"
  	| srcName name length |
  	<var: #className type: #'char *'>
  	<var: #srcName type: #'char *'>
+ 	(objectMemory numSlotsOf: aClass) <= classNameIndex ifTrue:
- 	(objectMemory lengthOf: aClass) <= classNameIndex ifTrue:
  		[^ false]. "Not a class but might be behavior"
  	name := objectMemory fetchPointer: classNameIndex ofObject: aClass.
  	(objectMemory isBytes: name) ifFalse:
  		[^false].
+ 	length := self numBytesOfBytes: name.
- 	length := self stSizeOf: name.
  	srcName := self cCoerce: (self arrayValueOf: name) to: 'char *'.
  	0 to: length - 1 do: [:i | (srcName at: i) = (className at: i) ifFalse: [^false]].
  	"Check if className really ends at this point"
  	^(className at: length) = 0!

Item was changed:
  ----- Method: StackInterpreter>>primitiveAccessorDepthForExternalPrimitiveMethod: (in category 'primitive support') -----
  primitiveAccessorDepthForExternalPrimitiveMethod: methodObj
  	^(objectMemory integerValueOf:
  		(objectMemory
+ 			fetchPointer: ExternalCallLiteralFlagsIndex
+ 			ofObject: (self literal: 0 ofMethod: methodObj))) >>> SpurPrimitiveAccessorDepthShift!
- 			fetchPointer: 2
- 			ofObject: (self literal: 0 ofMethod: methodObj))) >>> 8!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>linkExternalCall:errInto: (in category 'plugin primitive support') -----
+ linkExternalCall: externalCallLiteral errInto: failPtr
+ 	<returnTypeC: 'void (*linkExternalCallerrInto(sqInt externalCallLiteral, sqInt *failPtr))()'>
+ 	<var: 'failPtr' type: #'sqInt *'>
+ 	"The function has not been loaded yet. Fetch module and function name."
+ 	| addr functionLength functionName index metadata moduleLength moduleName |
+ 	<inline: false>
+ 	<var: #addr declareC: 'void (*addr)()'>
+ 	moduleName := objectMemory fetchPointer: ExternalCallLiteralModuleNameIndex ofObject: externalCallLiteral.
+ 	moduleName = objectMemory nilObject
+ 		ifTrue: [moduleLength := 0]
+ 		ifFalse: [(objectMemory isBytes: moduleName) ifFalse:
+ 					[failPtr ifNotNil: [failPtr at: 0 put: PrimErrBadMethod].
+ 					 ^0].
+ 				moduleLength := objectMemory numBytesOfBytes: moduleName].
+ 	functionName := objectMemory fetchPointer: ExternalCallLiteralFunctionNameIndex ofObject: externalCallLiteral.
+ 	(objectMemory isBytes: functionName) ifFalse:
+ 		[failPtr ifNotNil: [failPtr at: 0 put: PrimErrBadMethod].
+ 		 ^0].
+ 	functionLength := objectMemory numBytesOfBytes: functionName.
+ 
+ 	"Spur needs metadata for the primitive, which is stored in the third slot of the literal."
+ 	objectMemory hasSpurMemoryManagerAPI
+ 		ifTrue:
+ 			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
+ 						OfLength: functionLength
+ 						FromModule: moduleName + objectMemory baseHeaderSize
+ 						OfLength: moduleLength
+ 						MetadataInto: (self addressOf: metadata
+ 												 put: [:val| metadata := val]).
+ 			 addr = 0
+ 				ifTrue: [index := -1]
+ 				ifFalse: "add the function to the external primitive table"
+ 					[self assert: (metadata >>> SpurPrimitiveAccessorDepthShift between: -1 and: 5).
+ 					 index := self addToExternalPrimitiveTable: addr.
+ 					 objectMemory
+ 						storePointerUnchecked: ExternalCallLiteralFlagsIndex
+ 						ofObject: externalCallLiteral
+ 						withValue: (objectMemory integerObjectOf: metadata)]]
+ 		ifFalse:
+ 			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
+ 						OfLength: functionLength
+ 						FromModule: moduleName + objectMemory baseHeaderSize
+ 						OfLength: moduleLength.
+ 			 addr = 0
+ 				ifTrue: [index := -1]
+ 				ifFalse: "add the function to the external primitive table"
+ 					[index := self addToExternalPrimitiveTable: addr]].
+ 
+ 	"Store the index (or -1 if failure) back in the literal"
+ 	objectMemory
+ 		storePointerUnchecked: ExternalCallLiteralTargetFunctionIndex
+ 		ofObject: externalCallLiteral
+ 		withValue: (objectMemory integerObjectOf: index).
+ 
+ 	"If the function has been successfully loaded cache it"
+ 	self rewriteMethodCacheEntryForExternalPrimitiveToFunction: (index >= 0
+ 																		ifTrue: [self cCode: [addr] inSmalltalk: [1000 + index]]
+ 																		ifFalse: [0]).
+ 	^addr!

Item was removed:
- ----- Method: StackInterpreterPrimitives>>linkExternalCall:ifFail: (in category 'plugin primitive support') -----
- linkExternalCall: externalCallLiteral ifFail: failBlock
- 	<inline: #always>
- 	"The function has not been loaded yet. Fetch module and function name."
- 	| addr functionLength functionName index metadata moduleLength moduleName |
- 	<var: #addr declareC: 'void (*addr)()'>
- 	moduleName := objectMemory fetchPointer: ExternalCallLiteralModuleNameIndex ofObject: externalCallLiteral.
- 	moduleName = objectMemory nilObject
- 		ifTrue: [moduleLength := 0]
- 		ifFalse: [(objectMemory isBytes: moduleName) ifFalse:
- 					[failBlock value.
- 					 ^0].
- 				moduleLength := objectMemory lengthOf: moduleName].
- 	functionName := objectMemory fetchPointer: ExternalCallLiteralFunctionNameIndex ofObject: externalCallLiteral.
- 	(objectMemory isBytes: functionName) ifFalse:
- 		[failBlock value.
- 		 ^0].
- 	functionLength := objectMemory lengthOf: functionName.
- 
- 	"Spur needs metadata for the primitive, which is stored in the third slot of the literal."
- 	objectMemory hasSpurMemoryManagerAPI
- 		ifTrue:
- 			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
- 						OfLength: functionLength
- 						FromModule: moduleName + objectMemory baseHeaderSize
- 						OfLength: moduleLength
- 						MetadataInto: (self addressOf: metadata
- 												 put: [:val| metadata := val]).
- 			 addr = 0
- 				ifTrue: [index := -1]
- 				ifFalse: "add the function to the external primitive table"
- 					[index := self addToExternalPrimitiveTable: addr.
- 					 objectMemory
- 						storePointerUnchecked: ExternalCallLiteralFlagsIndex
- 						ofObject: externalCallLiteral
- 						withValue: (objectMemory integerObjectOf: metadata)]]
- 		ifFalse:
- 			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
- 						OfLength: functionLength
- 						FromModule: moduleName + objectMemory baseHeaderSize
- 						OfLength: moduleLength.
- 			 addr = 0
- 				ifTrue: [index := -1]
- 				ifFalse: "add the function to the external primitive table"
- 					[index := self addToExternalPrimitiveTable: addr]].
- 
- 	"Store the index (or -1 if failure) back in the literal"
- 	objectMemory
- 		storePointerUnchecked: ExternalCallLiteralTargetFunctionIndex
- 		ofObject: externalCallLiteral
- 		withValue: (objectMemory integerObjectOf: index).
- 
- 	"If the function has been successfully loaded cache it"
- 	self rewriteMethodCacheEntryForExternalPrimitiveToFunction: (index >= 0
- 																		ifTrue: [self cCode: [addr] inSmalltalk: [1000 + index]]
- 																		ifFalse: [0]).
- 	^addr!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveDoNamedPrimitiveWithArgs (in category 'plugin primitives') -----
  primitiveDoNamedPrimitiveWithArgs
  	"Simulate an primitiveExternalCall invocation (e.g. for the Debugger).  Do not cache anything.
  	 e.g. ContextPart>>tryNamedPrimitiveIn: aCompiledMethod for: aReceiver withArgs: arguments"
  	| argumentArray arraySize methodArg methodHeader
  	  moduleName functionName moduleLength functionLength
  	  spec addr primRcvr isArray |
  	<var: #addr declareC: 'void (*addr)()'>
  	objectMemory hasSpurMemoryManagerAPI ifTrue: "See checkForAndFollowForwardedPrimitiveState"
  		[metaAccessorDepth := -2].
  	argumentArray := self stackTop.
  	methodArg := self stackValue: 2.
  	((objectMemory isArray: argumentArray)
  	 and: [objectMemory isOopCompiledMethod: methodArg]) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  	arraySize := objectMemory numSlotsOf: argumentArray.
  	(self roomToPushNArgs: arraySize) ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args"
  
  	methodHeader := objectMemory methodHeaderOf: methodArg.
  	(objectMemory literalCountOfMethodHeader: methodHeader) > 2 ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  	spec := objectMemory fetchPointer: 1 "first literal" ofObject: methodArg.
  	isArray := self isInstanceOfClassArray: spec.
  	(isArray
  	and: [(objectMemory numSlotsOf: spec) = 4
  	and: [(self primitiveIndexOfMethod: methodArg header: methodHeader) = PrimNumberExternalCall]]) ifFalse:
  		[^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	(self argumentCountOfMethodHeader: methodHeader) = arraySize ifFalse:
  		[^self primitiveFailFor: -2]. "invalid args (Array args wrong size)"
  
  	"The function has not been loaded yet. Fetch module and function name."
  	moduleName := objectMemory fetchPointer: 0 ofObject: spec.
  	moduleName = objectMemory nilObject
  		ifTrue: [moduleLength := 0]
  		ifFalse: [self success: (objectMemory isBytes: moduleName).
+ 				moduleLength := objectMemory numBytesOfBytes: moduleName].
- 				moduleLength := objectMemory lengthOf: moduleName].
  	functionName := objectMemory fetchPointer: 1 ofObject: spec.
  	self success: (objectMemory isBytes: functionName).
+ 	functionLength := objectMemory numBytesOfBytes: functionName.
- 	functionLength := objectMemory lengthOf: functionName.
  	self successful ifFalse: [^self primitiveFailFor: -3]. "invalid methodArg state"
  
  	"Spur needs to know the primitive's accessorDepth."
  	objectMemory hasSpurMemoryManagerAPI
  		ifTrue:
  			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
  						OfLength: functionLength
  						FromModule: moduleName + objectMemory baseHeaderSize
  						OfLength: moduleLength
  						MetadataInto: (self addressOf: metaAccessorDepth
  												 put: [:val| metaAccessorDepth := val]).
  			"N.B. the accessor depth is the second byte of the primitive's metadata;
  			 the first byte is various flags (currently l.s.b. = use fast C linkage)."
  			 metaAccessorDepth := addr = 0 ifTrue: [-2] ifFalse: [metaAccessorDepth bitShift: -8]]
  		ifFalse:
  			[addr := self ioLoadExternalFunction: functionName + objectMemory baseHeaderSize
  						OfLength: functionLength
  						FromModule: moduleName + objectMemory baseHeaderSize
  						OfLength: moduleLength].
  	addr = 0 ifTrue:
  		[^self primitiveFailFor: -1]. "could not find function; answer generic failure (see below)"
  
  	"Cannot fail this primitive from now on.  Can only fail the external primitive."
  	tempOop := objectMemory
  						eeInstantiateClassIndex: ClassArrayCompactIndex
  						format: objectMemory arrayFormat
  						numSlots: 4.
  	objectMemory
  		storePointerUnchecked: 0 ofObject: tempOop withValue: (argumentArray := self popStack);
  		storePointerUnchecked: 1 ofObject: tempOop withValue: (primRcvr := self popStack);
  		storePointerUnchecked: 2 ofObject: tempOop withValue: self popStack; "the method"
  		storePointerUnchecked: 3 ofObject: tempOop withValue: self popStack. "the context receiver"
  	self push: primRcvr. "replace context receiver with actual receiver"
  	argumentCount := arraySize.
  	1 to: arraySize do:
  		[:index| self push: (objectMemory fetchPointer: index - 1 ofObject: argumentArray)].
  	self callExternalPrimitive: addr.
  	self successful ifFalse: "If primitive failed, then restore state for failure code"
  		[self pop: arraySize + 1.
  		 self push: (objectMemory fetchPointer: 3 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 2 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 1 ofObject: tempOop).
  		 self push: (objectMemory fetchPointer: 0 ofObject: tempOop).
  		 argumentCount := 3.
  		 "Must reset primitiveFunctionPointer for checkForAndFollowForwardedPrimitiveState"
  		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[primitiveFunctionPointer := #primitiveDoNamedPrimitiveWithArgs].
  		 "Hack.  A nil prim error code (primErrorCode = 1) is interpreted by the image
  		  as meaning this primitive is not implemented.  So to pass back nil as an error
  		  code we use -1 to indicate generic failure."
  		 primFailCode = 1 ifTrue:
  			[primFailCode := -1]]!

Item was changed:
  ----- Method: StackInterpreterPrimitives>>primitiveExternalCall (in category 'plugin primitives') -----
  primitiveExternalCall
  	"Call an external primitive. External primitive methods first literals are an array of
  		* The module name (String | Symbol)
  		* The function name (String | Symbol)
  		* The session ID (SmallInteger) [OBSOLETE], or in Spur, the metadata (accessorDepth and flags; Integer))
  		* The function index (Integer) in the externalPrimitiveTable
  	For fast interpreter dispatch in subsequent invocations the primitiveFunctionPointer
  	in the method cache is rewritten, either to the function itself, or to zero if the external
  	function is not found.   This allows for fast responses as long as the method stays in
  	the cache. The cache rewrite relies on lastMethodCacheProbeWrite which is set in
  	addNewMethodToCache:.
  	Now that the VM flushes function addresses from its tables, the session ID is obsolete,
  	but it is kept for backward compatibility. Also, a failed lookup is reported specially. If a
  	method has been  looked up and not been found, the function address is stored as -1
  	(i.e., the SmallInteger -1 to distinguish from 16rFFFFFFFF which may be returned from
  	lookup), and the primitive fails with PrimErrNotFound."
  	| lit addr index |
  	
  	"Check for it being a method for primitiveDoPrimitiveWithArgs.
  	 Fetch the first literal of the method; check its an Array of length 4.
  	 Look at the function index in case it has been loaded before"
  	((objectMemory isOopCompiledMethod: newMethod)
  	 and: [(objectMemory literalCountOf: newMethod) > 0
  	 and: [lit := self literal: 0 ofMethod: newMethod.
  		(objectMemory isArray: lit)
  	 and: [(objectMemory numSlotsOf: lit) = 4
  	 and: [index := objectMemory fetchPointer: ExternalCallLiteralTargetFunctionIndex ofObject: lit.
  		objectMemory isIntegerObject: index]]]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadMethod].
  
  	index := objectMemory integerValueOf: index.
  	"Check if we have already looked up the function and failed."
  	index < 0 ifTrue:
  		["Function address was not found in this session, 
  		  Void the primitive function."
  		 self rewriteMethodCacheEntryForExternalPrimitiveToFunction: 0.
  		 ^self primitiveFailFor: PrimErrNotFound].
  
  	"Try to call the function directly"
  	(index > 0 and: [index <= MaxExternalPrimitiveTableSize]) ifTrue:
  		[addr := externalPrimitiveTable at: index - 1.
  		 addr ~= 0 ifTrue:
  			[self rewriteMethodCacheEntryForExternalPrimitiveToFunction: (self cCode: 'addr' inSmalltalk: [1000 + index]).
  			 self callExternalPrimitive: addr. "On Spur, sets primitiveFunctionPointer"
  			 self maybeRetryPrimitiveOnFailure.
  			 ^nil].
  		"if we get here, then an index to the external prim was 
  		kept on the ST side although the underlying prim 
  		table was already flushed"
  		^self primitiveFailFor: PrimErrNamedInternal].
  
  	"Clean up session id/metadata and external primitive index"
  	objectMemory storePointerUnchecked: ExternalCallLiteralFlagsIndex ofObject: lit withValue: ConstZero.
  	objectMemory storePointerUnchecked: ExternalCallLiteralTargetFunctionIndex ofObject: lit withValue: ConstZero.
  
  	"The function has not been loaded yet. Attempt to link it, cache it, and call it."
+ 	addr := self linkExternalCall: lit errInto: (self addressOf: primFailCode put: [:v| primFailCode := v]).
- 	addr := self linkExternalCall: lit ifFail: [^self primitiveFailFor: PrimErrBadMethod].
  	addr = 0 ifTrue:
  		[self assert: (objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit) = ConstZero.
+ 		 ^self primitiveFailFor: (primFailCode = 0 ifTrue: [PrimErrNotFound] ifFalse: [primFailCode])].
- 		 ^self primitiveFailFor: PrimErrNotFound].
  
  	self callExternalPrimitive: addr.
  	self maybeRetryPrimitiveOnFailure	!

Item was changed:
  ----- Method: StackInterpreterSimulator>>classNameOf:Is: (in category 'plugin support') -----
  classNameOf: aClass Is: className
  	"Check if aClass' name is className"
  	| name |
+ 	(objectMemory numSlotsOf: aClass) <= classNameIndex ifTrue:
- 	(objectMemory lengthOf: aClass) <= classNameIndex ifTrue:
  		[^false]. "Not a class but maybe behavior" 
  	name := objectMemory fetchPointer: classNameIndex ofObject: aClass.
  	(objectMemory isBytes: name) ifFalse:
  		[^false].
  	^ className = (self stringOf: name)!

Item was changed:
  VMBasicConstants subclass: #VMSpurObjectRepresentationConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'BecameActiveClassFlag BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag SpurPrimitiveAccessorDepthShift SpurPrimitiveFlagsMask'
- 	classVariableNames: 'BecameActiveClassFlag BecameCompiledMethodFlag BecamePointerObjectFlag OldBecameNewFlag'
  	poolDictionaries: ''
  	category: 'VMMaker-Interpreter'!




More information about the Vm-dev mailing list