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

commits at source.squeak.org commits at source.squeak.org
Wed Feb 16 02:05:38 UTC 2022


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

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

Name: VMMaker.oscog-eem.3155
Author: eem
Time: 15 February 2022, 6:05:12.864638 pm
UUID: fd91ad7e-0787-428f-80f8-2a85e5a25026
Ancestors: VMMaker.oscog-eem.3154

CoInterpreter: Fix issues with the PrimCallXXX flags. PrimCallIsInternalPrim wasn't initialized!! PrimCallIsExternalCall isn't used.  PrimCallIsInternalPrim should be set on all numbered primitives except FFI & named primitive primitives.

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

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.
+ 	PrimCallMayEndureCodeCompaction := 8.
+ 	PrimCallCollectsProfileSamples := 16.
+ 	PrimCallIsInternalPrim := 32.
- 	PrimCallIsExternalCall := 4.
- 	PrimCallNeedsNewMethod := 8.
- 	PrimCallMayEndureCodeCompaction := 16.
- 	PrimCallCollectsProfileSamples := 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 changed:
  ----- Method: CoInterpreter>>primitivePropertyFlagsForV3:numArgs: (in category 'cog jit support') -----
  primitivePropertyFlagsForV3: primIndex numArgs: numArgs
  	<inline: true>
  	"Answer any special requirements of the given primitive"
  	| baseFlags |
  	baseFlags := profileSemaphore ~= objectMemory nilObject
  					ifTrue: [PrimCallNeedsNewMethod + PrimCallCollectsProfileSamples]
  					ifFalse: [0].
  
  	self cppIf: #LRPCheck
  		ifTrue:
  			[longRunningPrimitiveCheckSemaphore ifNotNil:
  				[baseFlags := baseFlags bitOr: PrimCallNeedsNewMethod]].
  
+ 	((self isCalloutPrimitiveIndex: primIndex)
+ 	 or: [self isCodeCompactingPrimitiveIndex: primIndex]) ifTrue:
- 	(self isCalloutPrimitiveIndex: primIndex) ifTrue: "For callbacks & module unloading"
- 		[^baseFlags bitOr: PrimCallNeedsNewMethod + PrimCallMayEndureCodeCompaction + PrimCallIsExternalCall].
- 	(self isCodeCompactingPrimitiveIndex: primIndex) ifTrue:
  		[^baseFlags bitOr: PrimCallNeedsNewMethod + PrimCallMayEndureCodeCompaction].
  	((self isPerformPrimitive: primIndex)
  	 or: [self isMetaPrimitiveIndex: primIndex]) ifTrue:
  		[^baseFlags bitOr: PrimCallNeedsNewMethod].
  	^baseFlags!

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 PrimCallIsInternalPrim 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 PrimCallIsExternalCall PrimCallIsInternalPrim PrimCallMayEndureCodeCompaction PrimCallNeedsNewMethod PrimCallOnSmalltalkStack PrimCallOnSmalltalkStackAlign2x ShouldNotJIT UnfailingPrimitive UnimplementedPrimitive YoungSelectorInPIC'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!

Item was changed:
  ----- Method: StackInterpreter class>>primitiveMetadataTableUsing: (in category 'constants') -----
  primitiveMetadataTableUsing: aCCodeGenerator
+ 	| slave |
+ 	slave := self basicNew.
+ 	^self primitiveTable collectWithIndex:
+ 		[:thing :index| | primitiveIndex implementingClass tMethod |
+ 		primitiveIndex := index - 1.
- 	^self primitiveTable collect:
- 		[:thing| | implementingClass tMethod |
  		(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)
+ 				+ ((slave isCalloutPrimitiveIndex: primitiveIndex) ifTrue: [0] ifFalse: [PrimCallIsInternalPrim])]]!
- 				+ (self metadataFlagsForPrimitive: tMethod)]]!



More information about the Vm-dev mailing list