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

commits at source.squeak.org commits at source.squeak.org
Tue Aug 2 16:40:27 UTC 2022


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

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

Name: VMMaker.oscog-eem.3232
Author: eem
Time: 2 August 2022, 9:40:11.234938 am
UUID: 054d025b-2745-4f1f-8a8b-af032b6c9841
Ancestors: VMMaker.oscog-eem.3231

ThreadedFFIPlugins:
Do inline ffiCall:ArgArrayOrNil:NumArgs:. We should err on teh side of speed.  The code size shouldn't affect icache performance because the primitiveCalloutWithArgs path is used very rarely in practice.

Have all plugins assign BytesPerWord in their initialize methods, to inline positiveMachineIntegerFor: et al.  Override InterpreterPlugin class>>#shouldGenerateDeadCode since these are very platform-specific and the dead code decision well under control.

Slang: fix isConstantNode:valueInto: to not be fooled by/ignore the cmacro part of macro methods.
Initialize generateDeadCode in VMPluginCodeGenerator>>#pluginClass:

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

Item was changed:
  ----- Method: CCodeGenerator>>isConstantNode:valueInto: (in category 'utilities') -----
  isConstantNode: aNode valueInto: aBlock
  	"Answer if aNode evaluates to a constant, and if so, evaluate aBlock with the value of that constant."
  
  	aNode isConstant ifTrue:
  		[(aNode isDefine
  		  and: [(vmClass ifNil: [VMBasicConstants]) defineAtCompileTime: aNode name]) ifTrue:
  			[^false].
  		 aBlock value: aNode value.
  		 ^true].
  	(aNode isVariable
  	 and: [aNode name = #nil]) ifTrue:
  		[aBlock value: nil.
  		 ^true].
  	aNode isSend ifTrue:
  		[(self anyMethodNamed: aNode selector)
  			ifNil:
  				[(VMBasicConstants valueOfBasicSelector: aNode selector) ifNotNil:
  					[:value|
  					 aBlock value: value.
  					 ^true].
  				 aNode constantNumbericValueOrNil ifNotNil:
  					[:value|
  					 aBlock value: value.
  					 ^true]]
  			ifNotNil:
  				[:m|
+ 				(m definedAsMacro not
+ 				 and: [m statements size = 1
+ 				 and: [m statements last isReturn]]) ifTrue:
- 				(m statements size = 1
- 				 and: [m statements last isReturn]) ifTrue:
  					[^self isConstantNode: m statements last expression valueInto: aBlock]]].
  	^false!

Item was changed:
  ----- Method: ThreadedARM32FFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
  	super initialize.
+ 	BytesPerWord := 4.
  	NumIntRegArgs := 4.
  	NumFloatRegArgs := 16!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
  	super initialize.
+ 	BytesPerWord := 8.
  	NumIntRegArgs    := 8.
  	NumFloatRegArgs := 8!

Item was changed:
  ----- Method: ThreadedFFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
  	"c.f. ExternalFunction allInstVarNames
  		old: #('handle' 'flags' 'argTypes')
  		new: #('handle' 'flags' 'argTypes' 'stackSize')"
  	ExternalFunctionAddressIndex := 0.
  	ExternalFunctionFlagsIndex := 1.
  	ExternalFunctionArgTypesIndex := 2.
  	ExternalFunctionStackSizeIndex := 3.
  
  	"c.f. e.g. CoInterpreter class initializeMiscConstants"
  	MaxNumArgs := 15.
  
  	DefaultMaxStackSize := 1024 * 16.
  
  	PluginVersionInfo := CCodeGenerator shortMonticelloDescriptionForClass: self.
+ 	PluginVersionInfo := PluginVersionInfo allButFirst: (PluginVersionInfo indexOf: Character space) - 1.
+ 
+ 	BytesPerWord := #subclassResponsibility "i.e. every subclass must define this explicitly"!
- 	PluginVersionInfo := PluginVersionInfo allButFirst: (PluginVersionInfo indexOf: Character space) - 1!

Item was added:
+ ----- Method: ThreadedFFIPlugin class>>shouldGenerateDeadCode (in category 'translation') -----
+ shouldGenerateDeadCode
+ 	"Answer if the code generator should generate dead code, e.g. in false ifTrue: [dead] ifFalse: [live].
+ 	 Since plugin source is shared between different VM builds it is unsafe to assume any code is dead.
+ 	 However, theThreadedFFIPlugin is much more platform-specific and we've done a lot of work on
+ 	 inlining, so code which depends on defined-at-compiled-time constants should not be considered
+ 	 dead.  So..."
+ 
+ 	^false!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCall:ArgArrayOrNil:NumArgs: (in category 'callout support') -----
  ffiCall: externalFunction ArgArrayOrNil: argArrayOrNil NumArgs: nArgs
  	"Generic callout. Does the actual work.  If argArrayOrNil is nil it takes args from the stack
  	 and the spec from the method.  If argArrayOrNil is not nil takes args from argArrayOrNil
  	 and the spec from the receiver."
  	| flags argTypeArray address argType oop argSpec argClass err theCalloutState calloutState requiredStackSize stackSize allocation result primNumArgs |
+ 	<inline: #always>
- 	<inline: false>
  	<var: #theCalloutState type: #'CalloutState'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #allocation type: #'char *'>
  
  	primNumArgs := interpreterProxy methodArgumentCount.
  	(interpreterProxy is: externalFunction KindOfClass: interpreterProxy classExternalFunction) ifFalse:
  		[^self ffiFail: FFIErrorNotFunction].
  	"Load and check the values in the externalFunction before we call out"
  	flags := interpreterProxy fetchInteger: ExternalFunctionFlagsIndex ofObject: externalFunction.
  	interpreterProxy failed ifTrue:
  		[^self ffiFail: FFIErrorBadArgs].
  
  	"This must come early for compatibility with the old FFIPlugin.  Image-level code
  	 may assume the function pointer is loaded eagerly.  Thanks to Nicolas Cellier."
  	address := self ffiLoadCalloutAddress: externalFunction.
  	interpreterProxy failed ifTrue:
  		[^0 "error code already set by ffiLoadCalloutAddress:"].
  	
  	argTypeArray := interpreterProxy fetchPointer: ExternalFunctionArgTypesIndex ofObject: externalFunction.
  	"must be array of arg types"
  	((interpreterProxy isArray: argTypeArray)
  	and: [(interpreterProxy slotSizeOf: argTypeArray) = (nArgs + 1)]) ifFalse:
  		[^self ffiFail: FFIErrorBadArgs].
  	"check if the calling convention is supported"
  	self cppIf: COGMTVM
  		ifTrue:
  			[(self ffiSupportsCallingConvention: (flags bitAnd: FFICallTypesMask)) ifFalse:
  				[^self ffiFail: FFIErrorCallType]]
  		ifFalse: "not masking causes threaded calls to fail, which is as they should if the plugin is not threaded."
  			[(self ffiSupportsCallingConvention: flags) ifFalse:
  				[^self ffiFail: FFIErrorCallType]].
  		
  	requiredStackSize := self externalFunctionHasStackSizeSlot
  							ifTrue: [interpreterProxy
  										fetchInteger: ExternalFunctionStackSizeIndex
  										ofObject: externalFunction]
  							ifFalse: [-1].
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: (argArrayOrNil isNil
  												ifTrue: [PrimErrBadMethod]
  												ifFalse: [PrimErrBadReceiver])].
  	stackSize := requiredStackSize < 0 ifTrue: [DefaultMaxStackSize] ifFalse: [requiredStackSize].
  	self cCode: [] inSmalltalk: [theCalloutState := self class calloutStateClass new].
  	calloutState := self addressOf: theCalloutState.
  	self cCode: [self memset: calloutState _: 0 _: (self sizeof: #CalloutState)].
  	calloutState callFlags: flags.
  	"Fetch return type and args"
  	argType := interpreterProxy fetchPointer: 0 ofObject: argTypeArray.
  	argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
  	argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
  	(err := self ffiCheckReturn: argSpec With: argClass in: calloutState) ~= 0 ifTrue:
  		[^self ffiFail: err]. "cannot return"
  	"alloca the outgoing stack frame, leaving room for marshalling args, and including space for the return struct, if any.
  	Additional space reserved for saving register args like mandated by Win64 X64 or PPC ABI, will be managed by the call itself"
  	allocation := self alloca: stackSize + calloutState structReturnSize + self cStackAlignment.
  	self mustAlignStack ifTrue:
  		[allocation := self cCoerce: (allocation asUnsignedIntegerPtr bitClear: self cStackAlignment - 1) to: #'char *'].
  	calloutState
  		argVector: allocation;
  		currentArg: allocation;
  		limit: allocation + stackSize.
  	(self nonRegisterStructReturnIsViaImplicitFirstArgument
  	 and: [calloutState structReturnSize > 0
  	 and: [(self returnStructInRegisters: calloutState) not]]) ifTrue:
  		[err := self ffiPushPointer: calloutState limit in: calloutState.
  		 err ~= 0 ifTrue:
  			[self cleanupCalloutState: calloutState.
  			 self cppIf: COGMTVM ifTrue:
  			 [err = PrimErrObjectMayMove negated ifTrue:
  				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
  			 ^self ffiFail: err]].
  	1 to: nArgs do:
  		[:i|
  		argType := interpreterProxy fetchPointer: i ofObject: argTypeArray.
  		argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
  		argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
+ 		oop := argArrayOrNil
+ 				ifNil: [interpreterProxy stackValue: nArgs - i]
+ 				ifNotNil: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
- 		oop := argArrayOrNil isNil
- 				ifTrue: [interpreterProxy stackValue: nArgs - i]
- 				ifFalse: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
  		err := self ffiArgument: oop Spec: argSpec Class: argClass in: calloutState.
  		err ~= 0 ifTrue:
  			[self cleanupCalloutState: calloutState.
  			 self cppIf: COGMTVM ifTrue:
  			 [err = PrimErrObjectMayMove negated ifTrue:
  				[^PrimErrObjectMayMove]]. "N.B. Do not fail if object may move because caller will GC and retry."
  			 ^self ffiFail: err]]. "coercion failed or out of stack space"
  	"Failures must be reported back from ffiArgument:Spec:Class:in:.
  	 Should not fail from here on in."
  	self assert: interpreterProxy failed not.
  	self ffiLogCallout: externalFunction.
  	(requiredStackSize < 0
  	 and: [self externalFunctionHasStackSizeSlot]) ifTrue:
  		[stackSize := calloutState currentArg - calloutState argVector.
  		 interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction withValue: stackSize].
  	"Go out and call this guy"
  	result := self ffiCalloutTo: address SpecOnStack: argArrayOrNil notNil in: calloutState.
  	self cleanupCalloutState: calloutState.
  	"Can not safely use argumentCount (via e.g. methodReturnValue:) since it may have been changed by a callback."
  	interpreterProxy pop: primNumArgs + 1 thenPush: result. 
  	^result!

Item was added:
+ ----- Method: ThreadedIA32FFIPlugin class>>initialize (in category 'class initialization') -----
+ initialize
+ 	super initialize.
+ 	BytesPerWord := 4!

Item was removed:
- ----- Method: ThreadedRiscV64FFIPlugin class>>initialize (in category 'class initialization') -----
- initialize
- 	super initialize.
- 	NumIntRegArgs    := 8.
- 	NumFloatRegArgs := 8!

Item was changed:
  ----- Method: ThreadedX64FFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
+ 	BytesPerWord := WordSize := 8.
- 	WordSize := 8.
  	NumIntRegArgs := 6.
  	NumFloatRegArgs := 8!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
+ 	super initialize.
- 	WordSize := 8.
  	NumIntRegArgs := 6.
  	NumFloatRegArgs := 8!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin class>>initialize (in category 'class initialization') -----
  initialize
+ 	super initialize.
- 	WordSize := 8.
  	NumIntRegArgs := 4.
  	NumFloatRegArgs := 4!

Item was changed:
  ----- Method: VMBasicConstants class>>namesDefinedAtCompileTime (in category 'C translation') -----
  namesDefinedAtCompileTime
  	"Answer the set of names for variables that should be defined at compile time.
  	 Some of these get default values during simulation, and hence get defaulted in
  	 the various initializeMiscConstants methods.  But that they have values should
  	 /not/ cause the code generator to do dead code elimination based on their
  	 default values.  In particular, methods marked with <option: ANameDefinedAtCompileTime>
  	 will be emitted within #if defined(ANameDefinedAtCompileTime)...#endif.
  
  	And of course this is backwards.  We'd like to define names that are defined at translation time.
  	But doing so would entail defining (or referencing) hundreds of class and pool variables.  This way
  	is more manageable"
  	^#(VMBIGENDIAN
  		IMMUTABILITY
  		STACKVM COGVM COGMTVM SPURVM
  		PharoVM								"Pharo vs Squeak"
  		TerfVM VM_TICKER						"Terf vs Squeak & Qwaq/Teleplace/Terf high-priority thread support"
  		EnforceAccessControl					"Newspeak"
  		CheckRememberedInTrampoline		"IMMUTABILITY"
  		BIT_IDENTICAL_FLOATING_POINT PLATFORM_SPECIFIC_FLOATING_POINT	"Alternatives for using fdlibm for floating-point"
  		ITIMER_HEARTBEAT						"older linux's woultn't allow a higher priority thread, hence no threaded heartbeat."
  		TestingPrimitives
  		OBSOLETE_ALIEN_PRIMITIVES			"Ancient crap in the IA32ABI plugin"
  		LLDB									"As of lldb-370.0.42 Swift-3.1, passing function parameters to printOopsSuchThat fails with Internal error [IRForTarget]: Couldn't rewrite one of the arguments of a function call.  Turning off link time optimization with -fno-lto has no effect.  hence we define some debugging functions as being <option: LLDB>"
  		LRPCheck								"Optional checking for long running primitives"
  
+ 		"ThreadedFFIPlugin related"
+ 		ALLOCA_LIES_SO_SETSP_BEFORE_CALL PLATFORM_API_USES_CALLEE_POPS_CONVENTION SQUEAK_BUILTIN_PLUGIN STACK_ALIGN_BYTES
+ 
  		"processor related"
  		__ARM_ARCH__ __arm__ __arm32__ ARM32 __arm64__ ARM64
  		_M_I386 _X86_ i386 i486 i586 i686 __i386__ __386__ X86 I386
  		x86_64 __amd64 __x86_64 __amd64__ __x86_64__ _M_AMD64 _M_X64
  
  		__mips__ __mips
  		__powerpc __powerpc__ __powerpc64__ __POWERPC__
  		__ppc__ __ppc64__ __PPC__ __PPC64__
  		__sparc__ __sparc __sparc_v8__ __sparc_v9__ __sparcv8 __sparcv9
  
  		"Compiler brand related"
  
  		__ACK__
  		__CC_ARM
  		__clang__
  		__GNUC__
  		_MSC_VER
  		__ICC
  
  		__SUNPRO_C
  		
  		"os related"
  		ACORN
  
  		_AIX
  		__ANDROID__
  		__APPLE__
  		__BEOS__
  		__linux__
  		__MACH__
  		__MINGW32__
  		__FreeBSD__ __NetBSD__ __OpenBSD__
  		__osf__
  
  		EPLAN9
  		__unix__ __unix UNIX
  		WIN32 _WIN32 _WIN32_WCE
  		WIN64 _WIN64 _WIN64_WCE)!

Item was changed:
  ----- Method: VMPluginCodeGenerator>>pluginClass: (in category 'public') -----
  pluginClass: aPluginClass
  	"Set the plugin class and name when generating plugins.
  	 And for run-time use, answer the name string."
  	| packageId |
  	pluginClass := aPluginClass.
+ 	aPluginClass ifNotNil:
+ 		[generateDeadCode := aPluginClass shouldGenerateDeadCode].
  	packageId := self shortMonticelloDescriptionForClass: pluginClass.
  	(packageId beginsWith: pluginClass name) ifTrue:
  		[packageId := packageId allButFirst: pluginClass name size].
  	(packageId beginsWith: pluginClass moduleName) ifTrue:
  		[packageId := packageId allButFirst: pluginClass moduleName size].
  	^self declareModuleName: pluginClass moduleNameAndVersion, packageId!



More information about the Vm-dev mailing list