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

commits at source.squeak.org commits at source.squeak.org
Thu Feb 17 18:15:48 UTC 2022


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

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

Name: VMMaker.oscog-eem.3157
Author: eem
Time: 17 February 2022, 10:15:27.034566 am
UUID: 0a61a955-24e6-49bb-90ed-2e1021d31a5d
Ancestors: VMMaker.oscog-eem.3156

Spur CoInterpreter: it's neater to define PrimCallIsExternalCall and mix this in for primitiveCalloutToFFI and primitiveExternalCall than defining PrimCallIsInternalPrim and mixing it in to all internal primitives.  Hence add primCalloutIsExternal, and have primitiveUnloadModule reset primitiveCalloutPointer.

CoInterpreter Slang: make sure pool defines are included in cointerp.h otherwise there is nothing to catch these variables being changed and cogitXXX.c's getting out of sync with cointerp.c.

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

Item was changed:
  ----- Method: CCodeGenerator>>addConstantForBinding: (in category 'public') -----
  addConstantForBinding: variableBinding
  	"Add the pool variable to the code base as a constant."
+ 	constants
+ 		at: variableBinding key
+ 		put: ((useSymbolicConstants and: [self isCLiteral: variableBinding value])
- 	| node val |
- 	val := variableBinding value.
- 	node := (useSymbolicConstants and: [self isCLiteral: val])
  				ifTrue:[TDefineNode new
  							setName: variableBinding key
  							value: variableBinding value]
+ 				ifFalse:[TConstantNode new setValue: variableBinding value])!
- 				ifFalse:[TConstantNode new setValue: variableBinding value].
- 	constants at: variableBinding key put: node!

Item was added:
+ ----- Method: CCodeGenerator>>commonSharedPoolVariableNames (in category 'C code generator') -----
+ commonSharedPoolVariableNames
+ 	"Answer the names of pool variables (potentially) shared between the Cogit and the CoInterpreter, but not defined in interp.h"
+ 	| commonConstants cointerpPools cogitPools |
+ 	commonConstants := Set new.
+ 	cointerpPools := vmClass withAllSuperclasses
+ 						inject: Set new
+ 						into: [:them :class| them addAll: class poolDictionaryNames. them].
+ 	cogitPools := vmClass cogitClass withAllSuperclasses
+ 						inject: Set new
+ 						into: [:them :class| them addAll: class poolDictionaryNames. them].
+ 	(cointerpPools intersection: cogitPools) do:
+ 		[:poolName|
+ 		(Smalltalk at: poolName) classPool associationsDo:
+ 			[:binding|
+ 			 (self isCLiteral: binding value) ifTrue:
+ 				[commonConstants add: binding key]]].
+ 	#(initializeMiscConstants initializePrimitiveErrorCodes) do:
+ 		[:selector|
+ 		(VMClass class>>selector) literalsDo:
+ 			[:lit|
+ 			(lit isVariableBinding and: [lit key isString]) ifTrue:
+ 				[commonConstants remove: lit key ifAbsent: []]]].
+ 	VMBasicConstants mostBasicConstantNames do:
+ 		[:mbcn| commonConstants remove: mbcn ifAbsent: []].
+ 	^commonConstants!

Item was changed:
  ----- Method: CCodeGenerator>>emitCAPIExportHeaderOn: (in category 'C code generator') -----
  emitCAPIExportHeaderOn: aStream 
  	"Store prototype declarations for all API methods on the given stream."
  	| exportedAPIMethods usedConstants |
  	exportedAPIMethods := self sortMethods: (methods select: [:m| m isAPIMethod]).
  	exportedAPIMethods do:
  		[:m|
  		m static ifTrue:
  			[logger ensureCr; show: m selector, ' excluded from export API because it is static'; cr]].
  	exportedAPIMethods := exportedAPIMethods reject: [:m| m static].
  	self emitCFunctionPrototypes: exportedAPIMethods on: aStream.
  	self emitGlobalCVariablesOn: aStream.
+ 	usedConstants := self emitCMacros: exportedAPIMethods on: aStream.	
+ 	(vmClass notNil and: [vmClass hasCogit]) ifTrue:
+ 		[usedConstants addAll: self commonSharedPoolVariableNames].
- 	usedConstants := self emitCMacros: exportedAPIMethods on: aStream.
  	self emitCConstants: usedConstants on: aStream!

Item was changed:
  ----- Method: CCodeGenerator>>emitCConstantsOn: (in category 'C code generator') -----
  emitCConstantsOn: aStream 
  	"Store the global variable declarations on the given stream."
  	| unused |
  	unused := constants keys asSet.
  	"Don't generate any defines for the externally defined constants,
+ 	 STACKVM, COGVM, COGMTVM et al, unless they're actually used.
+ 	 Also don't generate the PrimErr defines; these must be taken from interp.h"
+ 	#(initializeMiscConstants initializePrimitiveErrorCodes) do:
+ 		[:selector|
+ 		(VMClass class>>selector) literalsDo:
+ 			[:lit|
+ 			(lit isVariableBinding and: [lit key isString]) ifTrue:
+ 				[unused add: lit key]]].
+ 	"and VMBasicConstants mostBasicConstantNames must be taken from interp.h"
+ 	unused addAll: VMBasicConstants mostBasicConstantNames.
- 	 STACKVM, COGVM, COGMTVM et al, unless they're actually used."
- 	(VMClass class>>#initializeMiscConstants) literalsDo:
- 		[:lit|
- 		(lit isVariableBinding and: [lit key isString]) ifTrue:
- 			[unused add: lit key]].
  	methods do:
  		[:meth|
  		meth declarations keysDo:
  			[:v|
  			(meth typeFor: v in: self) ifNotNil:
  				[:type| unused remove: type ifAbsent: []]].
  		unused remove: meth returnType ifAbsent: [].
  		meth parseTree nodesDo:
  			[:n| n isConstant ifTrue: [unused remove: n name ifAbsent: []]]].
  	unused copy do:
  		[:const|
  		(variableDeclarations anySatisfy: [:value| value includesSubstring: const]) ifTrue:
  			[unused remove: const ifAbsent: []]].
+ 		self emitCConstants: (constants keys reject: [:any| unused includes: any]) on: aStream!
- 	"and VMBasicConstants mostBasicConstantNames *must* be taken from interp.h"
- 	unused addAll: VMBasicConstants mostBasicConstantNames.
- 	self emitCConstants: (constants keys reject: [:any| unused includes: any]) on: aStream!

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 primCalloutIsExternal'
- 	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 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>>initializeMiscConstants (in category 'initialization') -----
  initializeMiscConstants
  
  	super initializeMiscConstants.
  	COGVM := true.
  
  	MinBackwardJumpCountForCompile := 40.
  
  	MaxNumArgs := 15.
  
  	PrimCallOnSmalltalkStack := 1. "Speed up simple external prims by avoiding stack switch"
  	PrimCallOnSmalltalkStackAlign2x := 2. "Align stack to a 2 x word size boundary, e.g. for MMX instructions etc"
+ 	PrimCallNeedsNewMethod := 4. "e.g. primitiveExternalCall and primitiveCalloutToFFI extract info from newMethod's first literal"
+ 	PrimCallMayEndureCodeCompaction := 8. "primitiveExternalCall and primitiveCalloutToFFI may invoke callbacks, hence may experience code compaction."
+ 	PrimCallCollectsProfileSamples := 16. "tells JIT to compile support for profiling primitives"
+ 	PrimCallIsExternalPrim := 32. "Whether a primitive is not included in the VM, but loaded dynamically.
+ 									Hence it can only be called through a CallFullRT."
- 	PrimCallNeedsNewMethod := 4.
- 	PrimCallMayEndureCodeCompaction := 8.
- 	PrimCallCollectsProfileSamples := 16.
- 	PrimCallIsInternalPrim := 32.
  
  	"Flags for use in primitiveMetadata: in external primitives, overlap with the PrimCallXXX flags above"
  	FastCPrimitiveFlag := 1.				"a.k.a. PrimCallOnSmalltalkStack"
  	FastCPrimitiveAlignForFloatsFlag := 2.	"a.k.a. PrimCallOnSmalltalkStackAlign2x"
  
  	"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 added:
+ ----- Method: CoInterpreter>>augmentPrimitiveCalloutMetadataFlags (in category 'plugin primitive support') -----
+ augmentPrimitiveCalloutMetadataFlags
+ 	"Find out whether SqueakFFIPrims is internal or external"
+ 	<inline: #always>
+ 	| index |
+ 	primCalloutIsExternal := true.
+ 	index := 1.
+ 	[(self ioListBuiltinModule: index)
+ 		ifNil: [^self]
+ 		ifNotNil:
+ 			[:moduleName|
+ 			(self strcmp: moduleName _: 'SqueakFFIPrims') = 0 ifTrue:
+ 				[primCalloutIsExternal := false]].
+ 	 index := index + 1.
+ 	 true] whileTrue!

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)'>
  	<inline: false>
  	| flags |
  	flagsPtr ifNotNil:
  		[flagsPtr at: 0 put: (flags := self primitivePropertyFlags: primitiveIndex numArgs: (self argumentCountOf: methodObj))].
  	primitiveIndex == PrimNumberFFICall ifTrue:
+ 		[self functionForPrimitiveCallout. "first invocation sets primCalloutIsExternal"
+ 		 flagsPtr ifNotNil:
+ 			[primCalloutIsExternal ifTrue:
+ 				[flagsPtr at: 0 put: (flags bitOr: PrimCallIsExternalPrim)]].
+ 		 ^primitiveCalloutPointer].
- 		[^self functionForPrimitiveCallout].
  	primitiveIndex == PrimNumberExternalCall ifTrue:
  		[| lit |
  		 lit := self attemptToLinkExternalPrimitive: methodObj.
  		 flagsPtr ifNotNil:
  			["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:
  				[| metadata metadataFlags |
  				 metadata := objectMemory fetchPointer: ExternalCallLiteralFlagsIndex ofObject: lit.
  			 	 (objectMemory isIntegerObject: metadata) ifTrue:
  					[metadataFlags := (objectMemory integerValueOf: metadata) bitAnd: SpurPrimitiveFlagsMask.
  					 "combine the specific external primitive's flags with the base flags.
  					  Hence e.g. if profiling is in effect (as indicated by PrimCallCollectsProfileSamples
  					  in the base flags) it remains in effect after combining the specific flags."
  					 flags := flags bitOr: metadataFlags]].
+ 			 (self externalCallLiteralModuleIsVM: lit) ifFalse:
+ 				[flags := flags bitOr: PrimCallIsExternalPrim].
- 			 (self externalCallLiteralModuleIsVM: lit) ifTrue:
- 				[flags := flags bitOr: PrimCallIsInternalPrim].
  			 flagsPtr at: 0 put: flags].
  		 ^self functionForPrimitiveExternalCall: methodObj].
  	^self functionPointerFor: primitiveIndex inClass: nil!

Item was changed:
  ----- Method: CoInterpreter>>primitivePropertyFlagsForSpur:numArgs: (in category 'cog jit support') -----
  primitivePropertyFlagsForSpur: primIndex numArgs: numArgs
  	<inline: true>
  	"Answer any special requirements of the given primitive.  Spur needs to set
  	 newMethod if and when a primitive fails so primitives can retry on failure due
  	 to forwarders, but this isn't done until failure. The primitiveMetadataTable
  	 is populated based on the primitiveMetadata: pragma in internal primitives."
  	| baseFlags |
  	baseFlags := profileSemaphore = objectMemory nilObject
  					ifTrue: [0]
  					ifFalse: [PrimCallCollectsProfileSamples].
  	self cppIf: #LRPCheck
  		ifTrue:
  			[longRunningPrimitiveCheckSemaphore ifNotNil:
  				[baseFlags := baseFlags bitOr: PrimCallNeedsNewMethod]].
  
  	(primIndex = PrimNumberVMParameter and: [numArgs = 1]) "vmParameterAt:" ifTrue:
+ 		[^baseFlags + PrimCallOnSmalltalkStack + PrimCallOnSmalltalkStackAlign2x].
- 		[^baseFlags + PrimCallOnSmalltalkStack + PrimCallOnSmalltalkStackAlign2x + PrimCallIsInternalPrim].
  
  	^baseFlags bitOr: ((primitiveMetadataTable at: primIndex) bitAnd: SpurPrimitiveFlagsMask)!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveUnloadModule (in category 'plugin primitives') -----
  primitiveUnloadModule
  	"Primitive. Unload the module with the given name.
  	 Reloading of the module will happen *later* automatically, when a 
  	 function from it is called. This is forced by invalidating all external
  	 primitive methods and activations in flushExternalPrimitives.
  	 N.B. since this is most likely a development time activity we don't care about performance."
  	<primitiveMetadata: #PrimCallMayEndureCodeCompaction>
+ 	| moduleName moduleLength |
- 	| moduleName |
  	moduleName := self stackTop.
  	(objectMemory isBytes: moduleName) ifFalse:[^self primitiveFail].
+ 	moduleLength := objectMemory numBytesOfBytes: moduleName.
  	(self ioUnloadModule: (self oopForPointer: (objectMemory firstIndexableField: moduleName))
+ 		OfLength: moduleLength) ifFalse:[^self primitiveFail].
+ 	(self object: moduleName equalsString: 'SqueakFFIPrims' ofSize: moduleLength) ifTrue:
+ 		[primitiveCalloutPointer := self cCoerceSimple: -1 to: #'void *'].
- 		OfLength: (objectMemory numBytesOfBytes: moduleName)) ifFalse:[^self primitiveFail].
  	"N.B. flushExternalPrimitives continues.  Do *not* do anything after flushExternalPrimitives in the CoInterpreter"
  	self forceInterruptCheck.
  	self flushExternalPrimitives
  	"NOTREACHED"!

Item was changed:
  SharedPool subclass: #CogMethodConstants
  	instanceVariableNames: ''
+ 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMOpenPIC CompletePrimitive EncounteredUnknownBytecode InsufficientCodeSpace MaxLiteralCountForCompile MaxMethodSize MaxNegativeErrorCode MaxNumArgs MaxStackCheckOffset MethodTooBig NotFullyInitialized PrimCallCollectsProfileSamples PrimCallIsExternalPrim PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod PrimCallOnSmalltalkStack PrimCallOnSmalltalkStackAlign2x ShouldNotJIT UnfailingPrimitive UnimplementedPrimitive YoungSelectorInPIC'
- 	classVariableNames: 'CMBlock CMClosedPIC CMFree CMMaxUsageCount CMMethod CMOpenPIC CompletePrimitive EncounteredUnknownBytecode InsufficientCodeSpace MaxLiteralCountForCompile MaxMethodSize MaxNegativeErrorCode MaxNumArgs MaxStackCheckOffset MethodTooBig NotFullyInitialized PrimCallCollectsProfileSamples PrimCallIsInternalPrim PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod PrimCallOnSmalltalkStack PrimCallOnSmalltalkStackAlign2x ShouldNotJIT UnfailingPrimitive UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

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 jmpFail 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: nil arg: nil arg: nil arg: nil.
  	"If the primitive is in the interpreter then its address won't change relative to the code zone over time,
  	 whereas if it is in a plugin its address could change if the module is un/re/over/loaded.
  	 So if in the interpreter and in range use a normal call instruction."
+ 	((flags noMask: PrimCallIsExternalPrim)
- 	((flags anyMask: PrimCallIsInternalPrim)
  	 and: [backEnd isWithinCallRange: primitiveRoutine asInteger])
  		ifTrue: [self CallRT: primitiveRoutine asInteger]
  		ifFalse: [self CallFullRT: primitiveRoutine asInteger].
  	backEnd genRemoveNArgsFromStack: 0.
  	"test primFailCode and jump to failure sequence if non-zero"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	spRegSaveRegister ~= NoReg ifTrue:
  		[self MoveR: spRegSaveRegister R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmpFail := 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].
  
  	"primitive failure. if there is an accessor depth, scan and retry on failure (but what if faling for out of memory?)"
  	jmpFail jmpTarget: self Label.
  	(coInterpreter accessorDepthForPrimitiveMethod: 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.
  			(backEnd isWithinCallRange: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  										inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]))
  				ifTrue:
  					[self CallRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  										inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState])]
  				ifFalse:
  					[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 hasLinkRegister
  					ifTrue:
  						[self MoveAw: coInterpreter stackPointerAddress R: SPReg]
  					ifFalse: "remember to include return address; use scratch to avoid an interrupt overwriting retpc"
  						[self MoveAw: coInterpreter stackPointerAddress R: TempReg.
  						 self SubCq: objectRepresentation wordSize R: TempReg.
  						 self MoveR: TempReg R: SPReg]]].
  	"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: StackInterpreter class>>primitiveMetadataTableUsing: (in category 'constants') -----
  primitiveMetadataTableUsing: aCCodeGenerator
+ 	^self primitiveTable collect:
+ 		[:thing| | implementingClass tMethod |
- 	| slave |
- 	slave := self basicNew.
- 	^self primitiveTable collectWithIndex:
- 		[:thing :index| | primitiveIndex implementingClass tMethod |
- 		primitiveIndex := index - 1.
  		(thing isInteger "quick prims, 0 for fast primitve fail"
  		 or: [thing == #primitiveFail
  		 or: [(implementingClass := self primitivesClass whichClassIncludesSelector: thing) isNil]])
  			ifTrue: [-1 << SpurPrimitiveAccessorDepthShift]
  			ifFalse:
  				[tMethod := (aCCodeGenerator methodNamed: thing) ifNil:
  								[aCCodeGenerator compileToTMethodSelector: thing in: implementingClass].
  				 (aCCodeGenerator accessorDepthForMethod: tMethod) << SpurPrimitiveAccessorDepthShift
+ 				+ (self metadataFlagsForPrimitive: tMethod)]]!
- 				+ (self metadataFlagsForPrimitive: tMethod)
- 				+ ((slave isCalloutPrimitiveIndex: primitiveIndex) ifTrue: [0] ifFalse: [PrimCallIsInternalPrim])]]!

Item was added:
+ ----- Method: StackInterpreter>>augmentPrimitiveCalloutMetadataFlags (in category 'plugin primitive support') -----
+ augmentPrimitiveCalloutMetadataFlags
+ 	"noop in the StackInterpreter"
+ 	<inline: #always>!

Item was changed:
  ----- Method: StackInterpreter>>computeAccessorDepthsForInterpreterPrimitives (in category 'primitive support') -----
  computeAccessorDepthsForInterpreterPrimitives
  	<doNotGenerate>
  	| cg |
  	cg := self codeGeneratorToComputeAccessorDepth.
  	primitiveMetadataTable ifNil:
  		[primitiveMetadataTable := Array new: primitiveTable size withAll: (-1 bitShift: SpurPrimitiveAccessorDepthShift)].		
  	primitiveTable withIndexDo:
  		[:prim :index| | depthAndFlags |
  		 prim isSymbol ifTrue:
  			[depthAndFlags := self metadataFlagsFor: prim using: cg.
  			 self assert: depthAndFlags isInteger.
- 			 (self isCalloutPrimitiveIndex: index) ifFalse:
- 				[depthAndFlags := depthAndFlags bitOr: PrimCallIsInternalPrim].
  			 primitiveMetadataTable at: index - 1 put: depthAndFlags]].
  	^cg!

Item was changed:
  ----- Method: StackInterpreter>>functionForPrimitiveCallout (in category 'plugin primitive support') -----
  functionForPrimitiveCallout
  	"Answer the function primitiveCallout from the FFI plugin or nil if it can't
  	 be found.  Cache it for performance.  We use this circumlocution so that
  	 Squeak can be deployed without the FFI plugin for security reasons."
  
  	<returnTypeC: 'void (*functionForPrimitiveCallout())(void)'>
  	<inline: true>
  	primitiveCalloutPointer asInteger = -1 ifTrue:
+ 		[primitiveCalloutPointer := self ioLoadFunction: 'primitiveCallout' From: 'SqueakFFIPrims'.
+ 		 self augmentPrimitiveCalloutMetadataFlags].
- 		[primitiveCalloutPointer := self ioLoadFunction: 'primitiveCallout' From: 'SqueakFFIPrims'].
  	^self cCoerceSimple: primitiveCalloutPointer to: #'void (*)(void)'!

Item was added:
+ ----- Method: StackInterpreterPrimitives>>primitiveUnloadModule (in category 'plugin primitives') -----
+ primitiveUnloadModule
+ 	"Primitive. Unload the module with the given name.
+ 	 Reloading of the module will happen *later* automatically, when a 
+ 	 function from it is called. This is forced by invalidating all external
+ 	 primitive methods and activations in flushExternalPrimitives.
+ 	 N.B. since this is most likely a development time activity we don't care about performance."
+ 	<primitiveMetadata: #PrimCallMayEndureCodeCompaction>
+ 	| moduleName moduleLength |
+ 	moduleName := self stackTop.
+ 	(objectMemory isBytes: moduleName) ifFalse:[^self primitiveFail].
+ 	moduleLength := objectMemory numBytesOfBytes: moduleName.
+ 	(self ioUnloadModule: (self oopForPointer: (objectMemory firstIndexableField: moduleName))
+ 		OfLength: moduleLength) ifFalse:[^self primitiveFail].
+ 	(self object: moduleName equalsString: 'SqueakFFIPrims' ofSize: moduleLength) ifTrue:
+ 		[primitiveCalloutPointer := self cCoerceSimple: -1 to: #'void *'].
+ 	self forceInterruptCheck.
+ 	self flushExternalPrimitives.
+ 	self pop: 1 "pop moduleName; return receiver"!



More information about the Vm-dev mailing list