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

commits at source.squeak.org commits at source.squeak.org
Thu Aug 19 23:51:52 UTC 2021


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

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

Name: VMMaker.oscog-eem.3041
Author: eem
Time: 19 August 2021, 4:51:42.995965 pm
UUID: d49739b7-03f7-49a6-817b-f6f232342ad7
Ancestors: VMMaker.oscog-mt.3040

Cogit: nuke the one instance of a C ABI interpreter primitive, mcprimHashMultiply:.  It now has a machien code implementation and so the interpreter version and its support machinery are now dead weight.  Replace this by setting the FastCPrimitive flag for CompiledCode>>#objectAt:put:, primitiveObjectAtPut, which is good for about a 4% speedup for e.g. Morph compileAll.

=============== Diff against VMMaker.oscog-mt.3040 ===============

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
  	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer CReturnAddress primTracePluginName'
+ 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberObjectAtPut PrimTraceLogSize PrimitiveMetadataFlagsShift RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
- 	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize PrimitiveMetadataFlagsShift RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CoInterpreter commentStamp: 'eem 3/31/2020 18:56' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
  	- the names associated with the codes of events in traceLog
  
  CFramePointer
  	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CStackPointer
  	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
  
  CReturnAddress
  	- the return address for the function call which invoked the interpreter at start-up.  Using this as teh return address when entering the interpreter via ceInvokeInterpeter maintains a valid stack.  Since this is effevtively a constant it does not need to be saved and restored once set.!

Item was changed:
  ----- Method: CoInterpreter class>>initializePrimitiveTable (in category 'initialization') -----
  initializePrimitiveTable
  	super initializePrimitiveTable.
+ 	PrimNumberObjectAtPut := 69.
+ 	self assert: (PrimitiveTable at: PrimNumberObjectAtPut + 1) = #primitiveObjectAtPut.
- 	PrimNumberHashMultiply := 159.
- 	self assert: (PrimitiveTable at: PrimNumberHashMultiply + 1) = #primitiveHashMultiply.
  
  	#(216 253) do:
  		[:pidx| self assert: (PrimitiveTable at: pidx + 1) = #primitiveFail].
  	self assert: (PrimitiveTable at: 215 + 1) = #primitiveFlushCacheByMethod.
  	PrimitiveTable
  		at: 253 + 1 put: #primitiveCollectCogCodeConstituents;
  		at: 215 + 1 put: #primitiveVoidVMStateForMethod;
  		at: 216 + 1 put: #primitiveMethodXray!

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!

Item was added:
+ ----- Method: CoInterpreter>>accessorDepthForPrimitiveMethod: (in category 'cog jit support') -----
+ accessorDepthForPrimitiveMethod: aMethodObj
+ 	<api>
+ 	<option: #SpurObjectMemory>
+ 	| primIndex |
+ 	primIndex := self primitiveIndexOf: aMethodObj.
+ 	^primIndex = PrimNumberExternalCall
+ 		ifTrue: [self accessorDepthForExternalPrimitiveMethod: aMethodObj]
+ 		ifFalse: [self accessorDepthForPrimitiveIndex: primIndex]!

Item was removed:
- ----- Method: CoInterpreter>>mcprimFunctionForPrimitiveIndex: (in category 'cog jit support') -----
- mcprimFunctionForPrimitiveIndex: primIndex
- 	<api>
- 	primIndex = PrimNumberHashMultiply ifTrue:
- 		[^self cCoerceSimple: #mcprimHashMultiply: to: #sqInt].
- 	self error: 'unknown mcprim'.
- 	^nil!

Item was removed:
- ----- Method: CoInterpreter>>mcprims (in category 'cog jit support') -----
- mcprims
- 	<doNotGenerate>
- 	"Answer all the short-cut machine code primitives that run on the Smalltalk stack, not the C stack."
- 	^#(mcprimHashMultiply:)!

Item was changed:
  ----- Method: CoInterpreter>>primitivePropertyFlagsForSpur: (in category 'cog jit support') -----
  primitivePropertyFlagsForSpur: primIndex
  	<inline: true>
  	"Answer any special requirements of the given primitive.  Spur always needs to set
  	 primitiveFunctionPointer and newMethod so primitives can retry on failure due to forwarders."
  	| baseFlags |
+ 	self cCode: [] inSmalltalk: [#(primitiveObjectAtPut primitiveExternalCall primitiveCalloutToFFI)]. "For senders..."
+ 	baseFlags := profileSemaphore = objectMemory nilObject
+ 					ifTrue: [0]
+ 					ifFalse: [PrimCallCollectsProfileSamples].
+ 	primIndex = PrimNumberObjectAtPut ifTrue:
+ 		[^baseFlags + PrimCallOnSmalltalkStack].
+ 	baseFlags := baseFlags + PrimCallNeedsPrimitiveFunction + PrimCallNeedsNewMethod.
- 	self cCode: [] inSmalltalk: [#(mcprimHashMultiply: primitiveExternalCall primitiveCalloutToFFI)]. "For senders..."
- 	primIndex = PrimNumberHashMultiply ifTrue:
- 		[^PrimCallOnSmalltalkStack+FastCPrimitiveUseCABIFlag].
- 	baseFlags := PrimCallNeedsPrimitiveFunction + PrimCallNeedsNewMethod.
- 	profileSemaphore ~= objectMemory nilObject ifTrue:
- 		[baseFlags := baseFlags bitOr: PrimCallCollectsProfileSamples].
  
+ 	(self isCalloutPrimitiveIndex: primIndex) ifTrue: "For callbacks & module unloading"
+ 		[^baseFlags + PrimCallMayEndureCodeCompaction + PrimCallIsExternalCall].
+ 	(self isCodeCompactingPrimitiveIndex: primIndex) ifTrue: "For code reclamations"
+ 		[^baseFlags bitOr: PrimCallMayEndureCodeCompaction].
- 	(self isCalloutPrimitiveIndex: primIndex) "For callbacks & module unloading"
- 		ifTrue: [baseFlags := baseFlags bitOr: PrimCallMayEndureCodeCompaction + PrimCallIsExternalCall]
- 		ifFalse:
- 			[(self isCodeCompactingPrimitiveIndex: primIndex) ifTrue: "For code reclamations"
- 				[baseFlags := baseFlags bitOr: PrimCallMayEndureCodeCompaction]].
  
  	^baseFlags!

Item was removed:
- ----- Method: CoInterpreterPrimitives>>mcprimHashMultiply: (in category 'arithmetic primitives') -----
- mcprimHashMultiply: receiverArg
- 	"Machine code primitive for hash multiply. c.f. primitiveHashMultiply.
- 	 mcprims consume receiver and arguments as parameters and answer the
- 	 result on success, or set the primitive error code and answer 0 on failure."
- 	"Implement 28-bit hashMultiply for SmallInteger and LargePositiveInteger receivers."
- 	<api>
- 	| value |
- 	(objectMemory isIntegerObject: receiverArg)
- 		ifTrue: [value := objectMemory integerValueOf: receiverArg]
- 		ifFalse:
- 			[| ok |
- 			 ok := objectMemory is: receiverArg instanceOf: (objectMemory splObj: ClassLargePositiveInteger) compactClassIndex: ClassLargePositiveIntegerCompactIndex.
- 			 ok ifFalse:
- 				[self primitiveFailFor: PrimErrBadReceiver.
- 				 ^0].
- 			 value := objectMemory byteSwapped32IfBigEndian: (objectMemory fetchLong32: 0 ofObject: receiverArg)].
- 	^objectMemory integerObjectOf: (value * HashMultiplyConstant bitAnd: 16rFFFFFFF)!

Item was removed:
- ----- Method: CogVMSimulator>>mcprimFunctionForPrimitiveIndex: (in category 'cog jit support') -----
- mcprimFunctionForPrimitiveIndex: primIndex
- 	^self mapFunctionToAddress: (super mcprimFunctionForPrimitiveIndex: primIndex)!

Item was removed:
- ----- Method: CurrentImageCoInterpreterFacade>>mcprimFunctionForPrimitiveIndex: (in category 'accessing') -----
- mcprimFunctionForPrimitiveIndex: primIndex
- 	^self oopForObject: (coInterpreter mcprimFunctionForPrimitiveIndex: primIndex)!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>compileMachineCodeInterpreterPrimitive: (in category 'primitive generators') -----
- compileMachineCodeInterpreterPrimitive: primitiveRoutine
- 	"Compile a call to a machine-code convention interpreter primitive.  Call the C routine
- 	 on the Smalltalk stack, assuming it consumes little or no stack space."
- 	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
- 	| jmpFail liveRegsMask |
- 	"for now handle functions with less than 4 arguments; our C call marshalling machinery
- 	 extends up to 4 arguments only, and the first argument of an mcprim is the receiver."
- 	self assert: methodOrBlockNumArgs <= 3.
- 	liveRegsMask := (methodOrBlockNumArgs > self numRegArgs
- 					   or: [methodOrBlockNumArgs = 0])
- 						ifTrue:
- 							[self registerMaskFor: ReceiverResultReg]
- 						ifFalse:
- 							[(self numRegArgs > 1 and: [methodOrBlockNumArgs > 1])
- 								ifFalse: [self registerMaskFor: ReceiverResultReg and: Arg0Reg]
- 								ifTrue: [self registerMaskFor: ReceiverResultReg and: Arg0Reg and: Arg1Reg]].
- 	backEnd genSaveRegs: (liveRegsMask bitAnd: CallerSavedRegisterMask).
- 	methodOrBlockNumArgs > self numRegArgs ifTrue:
- 		["Wrangle args into Arg0Reg, Arg1Reg, SendNumArgsReg & ClassReg"
- 		 "offset := self bitCountOf: (liveRegsMask bitAnd: CallerSavedRegisterMask)."
- 		 self shouldBeImplemented].
- 	backEnd
- 		genMarshallNArgs: methodOrBlockNumArgs + 1
- 		arg: ReceiverResultReg
- 		arg: Arg0Reg
- 		arg: Arg1Reg
- 		arg: SendNumArgsReg
- 		"arg: ClassReg (when we extend C call marshalling to support 5 args for replaceFrom:to:with:startingAt:".
- 	backEnd saveAndRestoreLinkRegUsingCalleeSavedRegNotLiveAtPointOfSendAround:
- 		[self CallFullRT: primitiveRoutine asInteger].
- 	backEnd
- 		genRemoveNArgsFromStack: methodOrBlockNumArgs + 1;
- 		genRestoreRegs: (liveRegsMask bitAnd: CallerSavedRegisterMask).
- 	self CmpCq: 0 R: ABIResultReg.
- 	jmpFail := self JumpZero: 0.
- 	backEnd genWriteCResultIntoReg: ReceiverResultReg.
- 	self RetN: (methodOrBlockNumArgs > self numRegArgs
- 				ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
- 				ifFalse: [0]).
- 	jmpFail jmpTarget: self Label.
- 	^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."
  	<option: #SpurObjectMemory>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| calleeSavedRegisterMask linkRegSaveRegister spRegSaveRegister jmp retry continueAfterProfileSample jumpToTakeSample |
  	self assert: (objectRepresentation hasSpurMemoryManagerAPI and: [flags anyMask: PrimCallOnSmalltalkStack]).
  	self deny: (backEnd hasVarBaseRegister
  				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	(coInterpreter recordFastCCallPrimTraceForMethod: 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 AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  	self genExternalizeStackPointerForFastPrimitiveCall.
  	"We may need to save LinkReg and/or SPReg, and given the stack machinations
  	  it is much easier to save them in callee saved registers than on the stack itself."
  	calleeSavedRegisterMask := ABICalleeSavedRegisterMask bitClear: (self registerMaskFor: ClassReg).
  	backEnd hasLinkRegister ifTrue:
  		[linkRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: linkRegSaveRegister = NoReg.
  		 self MoveR: LinkReg R: linkRegSaveRegister.
  		 calleeSavedRegisterMask := calleeSavedRegisterMask bitClear: (self registerMaskFor: linkRegSaveRegister)].
  	spRegSaveRegister := NoReg.
  	(SPReg ~= NativeSPReg
  	 and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
  		[spRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: spRegSaveRegister = NoReg.
  		 self MoveR: SPReg R: spRegSaveRegister].
  	retry := self Label.
  	(flags anyMask: PrimCallOnSmalltalkStackAlign2x)
  		ifTrue: [self AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg]
  		ifFalse:
  			[SPReg ~= NativeSPReg ifTrue:
  				[backEnd genLoadNativeSPRegWithAlignedSPReg]].
  	backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  	self CallFullRT: primitiveRoutine asInteger.
  	backEnd genRemoveNArgsFromStack: 0.
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	spRegSaveRegister ~= NoReg ifTrue:
  		[self MoveR: spRegSaveRegister R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"Remember to restore the native stack pointer to point to the C stack,
  	 otherwise the Smalltalk frames will get overwritten on an interrupt."
  	SPReg ~= NativeSPReg ifTrue:
  		[backEnd genLoadCStackPointer].
  	"placing the test here attributes the tick to the primitive plus any checkForAndFollowForwardedPrimitiveState
  	 scanning, but attributes all of a failing primitive to the current method (in ceStackOverflow: on frame build)."
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg)].
  	"At this point the primitive has cut back stackPointer to point to the result."
  	continueAfterProfileSample :=
  	self MoveAw: coInterpreter stackPointerAddress R: TempReg.
  	"get result and restore retpc"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				AddCq: objectMemory wordSize R: TempReg R: SPReg;
  				MoveR: linkRegSaveRegister R: LinkReg]
  		ifFalse:
  			[| retpcOffset |
  			"The original retpc is (argumentCount + 1) words below stackPointer."
  			 retpcOffset := (methodOrBlockNumArgs + 1 * objectMemory wordSize) negated.
  			 self MoveMw: retpcOffset r: TempReg R: ClassReg; "get retpc"
  				MoveR: TempReg R: SPReg;
  			 	MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				MoveR: ClassReg Mw: 0 r: TempReg "put it back on stack for the return..."].
  	self RetN: 0.
  
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample jmpTarget: self Label.
  		 self genTakeProfileSample.
  		 self Jump: continueAfterProfileSample].
  
  	jmp jmpTarget: self Label.
+ 	(coInterpreter accessorDepthForPrimitiveMethod: methodObj) >= 0
- 	(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.
  			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.
  			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  			self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  								   inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]).
  			backEnd genLoadStackPointersForPrimCall: 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 genLoadStackPointersForPrimCall: ClassReg]].
  	"Remember to restore the native stack pointer to point to the C stack,
  	 otherwise the Smalltalk frames will get overwritten on an interrupt."
  	SPReg ~= NativeSPReg ifTrue:
  		[backEnd genLoadCStackPointer].
  	"The LinkRegister now contains the return address either of the primitive call or of checkForAndFollowForwardedPrimitiveState.
  	 It must be restored to the return address of the send invoking this primtiive method."
  	backEnd hasLinkRegister ifTrue:
  		[self MoveR: linkRegSaveRegister R: LinkReg].
  	"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: (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1])) * objectMemory wordSize
  			r: SPReg
  			R: ReceiverResultReg].
  	"continue to frame build..."
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compilePrimitive (in category 'primitive generators') -----
  compilePrimitive
  	"Compile a primitive.  If possible, performance-critical primitives will
  	 be generated by their own routines (primitiveGenerator).  Otherwise,
  	 if there is a primitive at all, we 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."
  	<inline: false>
  	| primitiveDescriptor primitiveRoutine flags |
  	<var: #primitiveDescriptor type: #'PrimitiveDescriptor *'>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	primitiveIndex = 0 ifTrue: [^0].
  	"If a descriptor specifies an argument count (by numArgs >= 0) then it must match
  	 for the generated code to be correct.  For example for speed many primitives use
  	 ResultReceiverReg instead of accessing the stack, so the receiver better be at
  	 numArgs down the stack.  Use the interpreter version if not."
  	((primitiveDescriptor := self primitiveGeneratorOrNil) notNil
  	 and: [primitiveDescriptor primitiveGenerator notNil
  	 and: [(primitiveDescriptor primNumArgs < 0 "means generator doesn't care"
  		   or: [primitiveDescriptor primNumArgs = (coInterpreter argumentCountOf: methodObj)])]]) ifTrue:
  		[| opcodeIndexAtPrimitive code |
  		"Note opcodeIndex so that any arg load instructions
  		 for unimplemented primitives can be discarded."
  		 opcodeIndexAtPrimitive := opcodeIndex.
  		 code := objectRepresentation perform: primitiveDescriptor primitiveGenerator.
  
  		(code < 0 and: [code ~= UnimplementedPrimitive]) ifTrue: "Generator failed, so no point continuing..."
  			[^code].
  		"If the primitive can never fail then there is nothing more that needs to be done."
  		code = UnfailingPrimitive ifTrue:
  			[^0].
  		"If the machine code version handles all cases the only reason to call the interpreter
  		 primitive is to reap the primitive error code.  Don't bother if it isn't used."
  		(code = CompletePrimitive
  		 and: [(self methodUsesPrimitiveErrorCode: methodObj header: methodHeader) not]) ifTrue:
  			[^0].
  		"Discard any arg load code generated by the primitive generator."
  		code = UnimplementedPrimitive ifTrue:
  			[opcodeIndex := opcodeIndexAtPrimitive]].
  
  	primitiveRoutine := coInterpreter
  							functionPointerForCompiledMethod: methodObj
  							primitiveIndex: primitiveIndex
  							primitivePropertyFlagsInto: (self addressOf: flags put: [:val| flags := val]).
  	(flags anyMask: PrimCallDoNotJIT) ifTrue:
  		[^ShouldNotJIT].
  
  	(primitiveRoutine = 0 "no primitive"
  	or: [primitiveRoutine = (self cCoerceSimple: #primitiveFail to: 'void (*)(void)')]) ifTrue:
  		[^self genFastPrimFail].
  
+ 	(objectRepresentation hasSpurMemoryManagerAPI
+ 	 and: [flags anyMask: PrimCallOnSmalltalkStack]) ifTrue:
+ 		[^self compileOnStackExternalPrimitive: primitiveRoutine flags: flags].
- 	(flags anyMask: PrimCallOnSmalltalkStack) ifTrue:
- 		[self deny: ((flags anyMask: FastCPrimitiveUseCABIFlag) and: [flags anyMask: PrimCallOnSmalltalkStackAlign2x]).
- 		(flags anyMask: FastCPrimitiveUseCABIFlag) ifTrue:
- 			[^self compileMachineCodeInterpreterPrimitive: (self cCoerceSimple: (coInterpreter mcprimFunctionForPrimitiveIndex: primitiveIndex)
- 															to: 'void (*)(void)')].
- 		objectRepresentation hasSpurMemoryManagerAPI ifTrue:
- 			[^self compileOnStackExternalPrimitive: primitiveRoutine flags: flags]].
  	minValidCallAddress := minValidCallAddress min: primitiveRoutine asUnsignedInteger.
  	^self compileInterpreterPrimitive: primitiveRoutine flags: flags!



More information about the Vm-dev mailing list