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

commits at source.squeak.org commits at source.squeak.org
Mon Jun 21 02:48:02 UTC 2021


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

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

Name: VMMaker.oscog-eem.2970
Author: eem
Time: 20 June 2021, 7:47:53.150975 pm
UUID: 18899133-c885-4672-8722-9faceaa8bd85
Ancestors: VMMaker.oscog-eem.2969

Merge VMMaker.oscog-dtl.2968.

Add support for tracing primitives in a single plugin.  The normal 256 element circular buffer is limited for tracking down plugin bugs because there is so much noise (context switches, other primitives, etc, etc).  So if the primTracePluginName is non-nil only calls of primitives within that plugin are logged (plus a handful of other potentially significant events).  This successfully traces primitives in e.g. the SoundPlugin:

primSoundAvailableBytes
primSoundPlaySamples:from:startingAt:
primSoundAvailableBytes
primSoundAvailableBytes
primSoundAvailableBytes
primSoundAvailableBytes
primSoundAvailableBytes
primSoundPlaySamples:from:startingAt:
primSoundAvailableBytes

stack page bytes 4096 available headroom 1480 minimum unused headroom 1912

	(SIGUSR1)

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

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'
- 	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'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize 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>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Override to avoid repeating StackInterpreter's declarations and add our own extensions"
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	aCCodeGenerator
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile: (aCCodeGenerator vmClass isThreadedVM 
  			ifTrue: ['"cointerpmt.h"'] 
  			ifFalse: ['"cointerp.h"']);
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator vmClass
  		declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: aCCodeGenerator interpreterVersion.
  	aCCodeGenerator
  		var: #heapBase type: #usqInt;
  		var: #statCodeCompactionUsecs type: #usqLong;
  		var: #maxLiteralCountForCompile
  			declareC: 'sqInt maxLiteralCountForCompile = MaxLiteralCountForCompile /* ', MaxLiteralCountForCompile printString, ' */';
  		var: #minBackwardJumpCountForCompile
  			declareC: 'sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* ', MinBackwardJumpCountForCompile printString, ' */'.
  	aCCodeGenerator
  		removeVariable: 'atCache'; "Way too much trouble than it's worth in the Cog VM"
  		removeVariable: 'reenterInterpreter'. "We can use the JIT and CFrame/StrackPointer for a lighter-weight solution."
  	aCCodeGenerator
  		var: #primTraceLogIndex type: #'unsigned char';
  		var: #primTraceLog declareC: 'sqInt primTraceLog[256]';
  		var: #traceLog
  		declareC: 'sqInt traceLog[TraceBufferSize /* ', TraceBufferSize printString, ' */]';
+ 		var: 'primTracePluginName' type: #'char *';
  		var: #traceSources type: #'char *' array: TraceSources.
  	aCCodeGenerator
  		var: #CFramePointer type: #'volatile usqIntptr_t';
  		var: #CStackPointer type: #'volatile usqIntptr_t';
  		var: #CReturnAddress type: #'volatile usqIntptr_t'!

Item was changed:
  ----- Method: CoInterpreter class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
  
  	^(super mustBeGlobal: var)
  	   or: [#('desiredCogCodeSize' 'heapBase'
+ 			'maxLiteralCountForCompile' 'minBackwardJumpCountForCompile'
+ 			'primTracePluginName') includes: var]!
- 			'maxLiteralCountForCompile' 'minBackwardJumpCountForCompile') includes: var]!

Item was changed:
  ----- Method: CoInterpreter>>ceCheckAndMaybeRetryPrimitive: (in category 'primitive support') -----
  ceCheckAndMaybeRetryPrimitive: primIndex
  	"Log failure and then retry if there's an accessorDepth or failure due to no memory."
  	<api>
  	<option: #SpurObjectMemory>
  	| retried |
+ 	(cogit recordPrimTrace and: [primTracePluginName isNil]) ifTrue:
- 	cogit recordPrimTrace ifTrue:
  		[self fastLogPrim: TracePrimitiveFailure].
  	retried := self retryPrimitiveOnFailure.
  	(retried and: [cogit recordPrimTrace]) ifTrue:
  		[self fastLogPrim: TracePrimitiveRetry]!

Item was changed:
  ----- Method: CoInterpreter>>checkForAndFollowForwardedPrimitiveState (in category 'primitive support') -----
  checkForAndFollowForwardedPrimitiveState
  	"Override to log"
  	<option: #SpurObjectMemory>
  	| found |
+ 	(cogit recordPrimTrace and: [primTracePluginName isNil]) ifTrue:
- 	cogit recordPrimTrace ifTrue:
  		[self fastLogPrim: TracePrimitiveFailure].
  	found := super checkForAndFollowForwardedPrimitiveState.
  	(found and: [cogit recordPrimTrace]) ifTrue:
  		[self fastLogPrim: TracePrimitiveRetry].
  	^found!

Item was changed:
  ----- Method: CoInterpreter>>maybeTraceStackOverflow (in category 'debug support') -----
  maybeTraceStackOverflow
  	cogit recordOverflowTrace ifTrue:
  		[self recordTrace: TraceStackOverflow
  			thing: TraceStackOverflow
  			source: ((self isMachineCodeFrame: framePointer)
  						ifTrue: [TraceIsFromMachineCode]
  						ifFalse: [TraceIsFromInterpreter])].
+ 	(cogit recordPrimTrace and: [primTracePluginName isNil]) ifTrue:
- 	cogit recordPrimTrace ifTrue:
  		[self fastLogPrim: TraceStackOverflow]!

Item was added:
+ ----- Method: CoInterpreter>>methodHasPrimitiveInPrimTracePlugin: (in category 'compiled methods') -----
+ methodHasPrimitiveInPrimTracePlugin: aMethodObj
+ 	<inline: #never>
+ 	| lit nameLength pluginName |
+ 	((self isExternalPrimitiveCall: aMethodObj)
+ 	 and: [(objectMemory literalCountOf: aMethodObj) > 0]) ifFalse:
+ 		[^false].
+ 	lit := self literal: 0 ofMethod: aMethodObj.
+ 	((objectMemory isArray: lit)
+ 	 and: [(objectMemory numSlotsOf: lit) = 4]) ifFalse:
+ 		[^false].
+ 	self assert: primTracePluginName notNil.
+ 	pluginName := objectMemory fetchPointer: 0 ofObject: lit.
+ 	(objectMemory isBytes: pluginName) ifFalse:
+ 		[^false].
+ 	nameLength := objectMemory numBytesOfBytes: pluginName.
+ 	^(self strncmp: primTracePluginName
+ 				_: (objectMemory firstIndexableField: pluginName)
+ 				_: nameLength) = 0
+ 	  and: [(self strlen: primTracePluginName) = nameLength]!

Item was changed:
  ----- Method: CoInterpreter>>recordContextSwitchFrom:in: (in category 'debug support') -----
  recordContextSwitchFrom: aProcess in: sourceCode
+ 	(cogit recordEventTrace and: [primTracePluginName isNil]) ifTrue:
- 	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceContextSwitch thing: aProcess source: sourceCode]!

Item was added:
+ ----- Method: CoInterpreter>>recordPrimTraceForMethod: (in category 'compiled methods') -----
+ recordPrimTraceForMethod: aMethodObj
+ 	"This is a little elaborate.  The primTraceLog is only useful if it is not full of noise.
+ 	 To reduce noise when debugging a specific plugin we allow a plugin name to be
+ 	 specified and will only generate the primTraceLog code for primitives in that plugin."
+ 	<api>
+ 	<inline: true>
+ 	^cogit recordPrimTrace
+ 	  and: [primTracePluginName
+ 				ifNil: [true]
+ 				ifNotNil: [self methodHasPrimitiveInPrimTracePlugin: aMethodObj]]!

Item was changed:
  ----- Method: CoInterpreter>>slowPrimitiveResponse (in category 'primitive support') -----
  slowPrimitiveResponse
  	"Invoke a normal (non-quick) primitive.
  	 Called under the assumption that primFunctionPointer has been preloaded.
  	 Override to log primitive."
+ 	(self recordPrimTraceForMethod: newMethod) ifTrue:
- 	cogit recordPrimTrace ifTrue:
  		[self fastLogPrim: messageSelector].
  	^super slowPrimitiveResponse!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  
  	aCCodeGenerator vmClass primitiveTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #primitiveGeneratorTable
  				declareC: 'static PrimitiveDescriptor primitiveGeneratorTable[MaxCompiledPrimitiveIndex+1]',
  							(self tableInitializerFor: aCCodeGenerator vmClass primitiveTable
  								in: aCCodeGenerator)].
  	aCCodeGenerator
  		var: #externalPrimCallOffsets
+ 			declareC: 'sqInt externalPrimCallOffsets[MaxNumArgs + MaxNumArgs + 2]';
- 			declareC: 'sqInt externalPrimCallOffsets[MaxNumArgs + 1]';
  		var: #externalPrimJumpOffsets
+ 			declareC: 'sqInt externalPrimJumpOffsets[MaxNumArgs + MaxNumArgs + 2]';
- 			declareC: 'sqInt externalPrimJumpOffsets[MaxNumArgs + 1]';
  		var: #externalSetPrimOffsets
+ 			declareC: 'sqInt externalSetPrimOffsets[MaxNumArgs + MaxNumArgs + 2]';
- 			declareC: 'sqInt externalSetPrimOffsets[MaxNumArgs + 1]';
  		var: #primSetFunctionLabel type: #'AbstractInstruction *';
  		var: #primInvokeInstruction type: #'AbstractInstruction *'!

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 |
  
  	"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:
- 	"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"
  	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.
  		 primSetFunctionLabel :=
  		 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]).
  			 primInvokeInstruction := 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.
  			primInvokeInstruction := 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>>recordCallOffsetIn: (in category 'external primitive support') -----
  recordCallOffsetIn: cogMethod
+ 	"Remember the offsets in an external primitive method where the function address is assigned
+ 	 to primitiveFunctionPointer (Spur) and where the external function is either called or jumped to.
+ 	 This allows the machine code to be unlinked when a plugin is unloaded, etc."
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
+ 	| index offset offsetTable |
- 	| offset offsetTable |
  	<var: #offsetTable type: #'sqInt *'>
  	offset := primSetFunctionLabel address - cogMethod asInteger.
+ 	index := (coInterpreter recordPrimTraceForMethod: cogMethod methodObject)
+ 				ifTrue: [cogMethod cmNumArgs + MaxNumArgs + 1]
+ 				ifFalse: [cogMethod cmNumArgs].
+ 	(externalSetPrimOffsets at: index)
+ 		ifNil: [externalSetPrimOffsets at: index put: offset]
+ 		ifNotNil: [self assert: (externalSetPrimOffsets at: index) = offset].
- 	(externalSetPrimOffsets at: cogMethod cmNumArgs) isNil
- 		ifTrue: [externalSetPrimOffsets at: cogMethod cmNumArgs put: offset]
- 		ifFalse: [self assert: (externalSetPrimOffsets at: cogMethod cmNumArgs) = offset].
  	offsetTable := primInvokeInstruction isJump
  						ifTrue: [externalPrimJumpOffsets]
  						ifFalse: [externalPrimCallOffsets].
  	offset := primInvokeInstruction address + primInvokeInstruction machineCodeSize - cogMethod asInteger.
+ 	(offsetTable at: index)
+ 		ifNil: [offsetTable at: index put: offset]
+ 		ifNotNil: [self assert: (offsetTable at: index) = offset]!
- 	(offsetTable at: cogMethod cmNumArgs) isNil
- 		ifTrue: [offsetTable at: cogMethod cmNumArgs put: offset]
- 		ifFalse: [self assert: (offsetTable at: cogMethod cmNumArgs) = offset]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>rewritePrimInvocationIn:to: (in category 'external primitive support') -----
  rewritePrimInvocationIn: cogMethod to: primFunctionPointer
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #primFunctionPointer declareC: #'void (*primFunctionPointer)(void)'>
+ 	| primIndex flags address extent index |
- 	| primIndex flags address extent |
  	self cCode: [] inSmalltalk:
  		[primFunctionPointer isInteger ifFalse:
  			[^self rewritePrimInvocationIn: cogMethod to: (self simulatedTrampolineFor: primFunctionPointer)]].
  	self assert: cogMethod cmType = CMMethod.
+ 	index := (coInterpreter recordPrimTraceForMethod: cogMethod methodObject)
+ 				ifTrue: [cogMethod cmNumArgs + MaxNumArgs + 1]
+ 				ifFalse: [cogMethod cmNumArgs].
  	primIndex := coInterpreter
  					primitiveIndexOfMethod: cogMethod methodObject
  					header: cogMethod methodHeader.
  	flags := coInterpreter primitivePropertyFlags: primIndex.
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[backEnd
  			storeLiteral: primFunctionPointer asUnsignedInteger
  			beforeFollowingAddress: cogMethod asUnsignedInteger
+ 									+ (externalSetPrimOffsets at: index)].
- 									+ (externalSetPrimOffsets at: cogMethod cmNumArgs)].
  	"See compileInterpreterPrimitive:"
  	(flags anyMask: PrimCallMayEndureCodeCompaction)
  		ifTrue:
  			[address := cogMethod asUnsignedInteger
+ 						+ (externalPrimJumpOffsets at: index).
- 						+ (externalPrimJumpOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteJumpFullAt: address
  						target: primFunctionPointer asUnsignedInteger]
  		ifFalse:
  			[address := cogMethod asUnsignedInteger
+ 						+ (externalPrimCallOffsets at: index).
- 						+ (externalPrimCallOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteCallFullAt: address
  						target: primFunctionPointer asUnsignedInteger].
  	extent > 0 ifTrue:
  		[backEnd
  			flushICacheFrom: cogMethod asUnsignedInteger + cmNoCheckEntryOffset
  			to: address asUnsignedInteger + extent]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>setInterpreter: (in category 'initialization') -----
  setInterpreter: aCoInterpreter
  	"Initialization of the code generator in the simulator.
  	 These objects already exist in the generated C VM
  	 or are used only in the simulation."
  	<doNotGenerate>
  	super setInterpreter: aCoInterpreter.
  	primitiveGeneratorTable := self class primitiveTable.
+ 	externalPrimJumpOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1 * 2).
+ 	externalPrimCallOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1 * 2).
+ 	externalSetPrimOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1 * 2)!
- 	externalPrimJumpOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1).
- 	externalPrimCallOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1).
- 	externalSetPrimOffsets := CArrayAccessor on: (Array new: MaxNumArgs + 1)!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>voidCogCompiledCode (in category 'jit - api') -----
  voidCogCompiledCode
  	<api>
  	methodZone clearCogCompiledCode.
+ 	0 to: MaxNumArgs + MaxNumArgs + 1 do:
- 	0 to: MaxNumArgs do:
  		[:i|
  		externalPrimJumpOffsets at: i put: nil.
  		externalPrimCallOffsets at: i put: nil.
  		externalSetPrimOffsets at: i put: nil]!

Item was changed:
  ----- Method: SpurMemoryManager>>numBytesOfBytes: (in category 'object access') -----
+ numBytesOfBytes: objOop
- numBytesOfBytes: objOop 
  	"Answer the number of indexable bytes in the given non-immediate byte-indexable object."
  	| fmt |
  	<inline: true>
  	fmt := self formatOf: objOop.
  	self assert: fmt >= self firstByteFormat.
  	^(self numSlotsOf: objOop) << self shiftForWord - (fmt bitAnd: 7)!

Item was changed:
  ----- Method: StackInterpreter>>initializeInterpreter: (in category 'initialization') -----
  initializeInterpreter: bytesToShift
  	"Initialize Interpreter state before starting execution of a new image."
  	interpreterProxy := self sqGetInterpreterProxy.
  	self dummyReferToProxy.
  	objectMemory initializeObjectMemory: bytesToShift.
  	self checkAssumedCompactClasses.
  	self initializeExtraClassInstVarIndices.
  	method := newMethod := objectMemory nilObject.
  	self cCode: '' inSmalltalk:
  		[breakSelectorLength ifNil:
  			[breakSelectorLength := objectMemory minSmallInteger].
  		 breakLookupClassTag ifNil: [breakLookupClassTag := -1].
  		 reenterInterpreter := ReenterInterpreter new].
  	methodDictLinearSearchLimit := 8.
  	self initialCleanup.
  	LowcodeVM ifTrue: [ self setupNativeStack ].
  	profileSemaphore := profileProcess := profileMethod := objectMemory nilObject.
  	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
  	[globalSessionID = 0] whileTrue:
  		[globalSessionID := self
+ 								cCode: [((self time: #NULL) + self ioMSecs) bitAnd: 16r7FFFFFFF]
+ 								inSmalltalk: [(Random new next * (SmallInteger maxVal min: 16r7FFFFFFF)) asInteger]].
- 								cCode: [(self time: #NULL) + self ioMSecs]
- 								inSmalltalk: [(Random new next * (SmallInteger maxVal min: 16rFFFFFFFF)) asInteger]].
  	metaAccessorDepth := -2.
  	super initializeInterpreter: bytesToShift!



More information about the Vm-dev mailing list