[Vm-dev] VM Maker: VMMaker.oscog-mt.3181.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 13 08:54:09 UTC 2022


Marcel Taeumel uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-mt.3181.mcz

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

Name: VMMaker.oscog-mt.3181
Author: mt
Time: 13 April 2022, 10:53:52.645201 am
UUID: 85dd23b6-7723-a548-811e-6356bd6d5095
Ancestors: VMMaker.oscog-mt.3179

In the FFI plugin, fixes a regression in int64_t support on 32-bit builds, which was due to a mix-up between int64_t and intptr_t.

Note that the current design only supports up to 64-bit integer types. If we want to support, for example, 128-bit integer types on a 64-bit machine, we would have to think about a replacement for 'usqLong'. Or even better, we find a way to specialize #ffiArgByValue:in: in subclasses of ThreadedFFIPlugin to use the stack more efficiently.

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

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiArgByValue:in: (in category 'callout support') -----
  ffiArgByValue: oop in: calloutState
  	"Support for generic callout. Prepare an argument by value for a callout."
  	<var: #calloutState type: #'CalloutState *'>
  	| atomicType intValue floatValue |
  	<inline: true>
+ 	<var: #intValue type: #'usqLong'> "Support up to int64_t or uint64_t"
  	atomicType := self atomicTypeOf: calloutState ffiArgHeader.
  	(self isFloatAtomicType: atomicType) ifFalse:
  		[intValue := self ffiIntegerValueOf: oop.
  		 interpreterProxy failed ifTrue:
  			[^FFIErrorCoercionFailed].
  		 "N.B. Slang inlines the functions within the dispatchOn:in:with:with: here-in"
  		 self cppIf: BytesPerWord = 8
  			ifTrue:
  				[^self dispatchOn: atomicType
  						in: #(
  							ffiPushVoid:in:					"FFITypeVoid"
  							ffiPushUnsigned64:in:			"FFITypeBool"
  							ffiPushUnsigned8:in:			"FFITypeUnsignedInt8"
  							ffiPushSigned8:in:				"FFITypeSignedInt8"
  							ffiPushUnsigned16:in:			"FFITypeUnsignedInt16"
  							ffiPushSigned16:in:				"FFITypeSignedInt16"
  							ffiPushUnsigned32:in:			"FFITypeUnsignedInt32"
  							ffiPushSigned32:in:				"FFITypeSignedInt32"
  							ffiPushUnsigned64:in:			"FFITypeUnsignedInt64"
  							ffiPushSigned64:in:				"FFITypeSignedInt64"
  							ffiPushUnsigned8:in:			"FFITypeUnsignedChar8"
  							ffiPushSigned8:in:				"FFITypeSignedChar8"
  							ffiPushVoid:in: "ffiPushFloat32:"	"FFITypeSingleFloat"
  							ffiPushVoid:in: "ffiPushFloat64:"	"FFITypeDoubleFloat"
  							ffiPushUnsigned16:in:			"FFITypeUnsignedChar16"
  							ffiPushUnsigned32:in:)			"FFITypeUnsignedChar32"
  						with: intValue
  						with: calloutState]
  			ifFalse:
  				[^self dispatchOn: atomicType
  						in: #(
  							ffiPushVoid:in:					"FFITypeVoid"
  							ffiPushUnsigned32:in:			"FFITypeBool"
  							ffiPushUnsigned8:in:			"FFITypeUnsignedInt8"
  							ffiPushSigned8:in:				"FFITypeSignedInt8"
  							ffiPushUnsigned16:in:			"FFITypeUnsignedInt16"
  							ffiPushSigned16:in:				"FFITypeSignedInt16"
  							ffiPushUnsigned32:in:			"FFITypeUnsignedInt32"
  							ffiPushSigned32:in:				"FFITypeSignedInt32"
  							ffiPushUnsigned64:in:			"FFITypeUnsignedInt64"
  							ffiPushSigned64:in: 			"FFITypeSignedInt64"
  							ffiPushUnsigned8:in:			"FFITypeUnsignedChar8"
  							ffiPushSigned8:in:				"FFITypeSignedChar8"
  							ffiPushVoid:in: "ffiPushFloat32:"	"FFITypeSingleFloat"
  							ffiPushVoid:in: "ffiPushFloat64:"	"FFITypeDoubleFloat"
  							ffiPushUnsigned16:in:			"FFITypeUnsignedChar16"
  							ffiPushUnsigned32:in:)			"FFITypeUnsignedChar32"
  						with: intValue
  						with: calloutState]].
  
  	floatValue := self ffiFloatValueOf: oop.
  	interpreterProxy failed ifTrue:
  		[^FFIErrorCoercionFailed].
  	atomicType = FFITypeSingleFloat
  		ifTrue: [^self ffiPushFloat32: floatValue in: calloutState]
  		ifFalse:[^self ffiPushFloat64: floatValue in: calloutState]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCreateIntegralResultOop:ofAtomicType:in: (in category 'callout support') -----
  ffiCreateIntegralResultOop: retVal ofAtomicType: atomicType in: calloutState
  	<inline: #always>
  	<var: 'calloutState' type: #'CalloutState *'>
+ 	<var: 'retVal' type: #usqLong> "Support up to int64_t or uint64_t"
- 	<var: 'retVal' type: #usqLong>
  	"Callout support. Return the appropriate oop for the given atomic type"
  	| shift value mask byteSize |
  	<var: 'value' type: #usqLong>
  	<var: 'mask' type: #usqLong>
  
  	self deny: (self isFloatAtomicType: atomicType).
  
  	atomicType = FFITypeBool ifTrue:
  		["Make sure bool honors the byte size requested"
  		 byteSize := calloutState ffiRetHeader bitAnd: FFIStructSizeMask.
  		 value := byteSize = (self sizeof: retVal)
  					ifTrue: [retVal]
  					ifFalse: [retVal bitAnd: 1 asUnsignedLongLong << (byteSize * 8) - 1].
  		 ^value = 0
  			ifTrue: [interpreterProxy falseObject]
  			ifFalse: [interpreterProxy trueObject]].
  	atomicType <= FFITypeSignedInt32 ifTrue:
  		["these are all generall integer returns"
  		atomicType <= (BytesPerWord = 8 ifTrue: [FFITypeSignedInt32] ifFalse: [FFITypeSignedInt16]) ifTrue:
  			["byte/short(/int). first extract partial word, then sign extend"
  			shift := (BytesPerWord = 8 and: [atomicType >= FFITypeUnsignedInt32])
  						ifTrue: [32]
  						ifFalse: [(atomicType >> 1) * 8]. "# of significant bits"
  			value := retVal bitAnd: (1 asUnsignedLongLong << shift - 1). 
  			(atomicType anyMask: 1) ifTrue:
  				["make the guy signed"
  				mask := 1 asUnsignedLongLong << (shift-1).
  				value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  			^interpreterProxy integerObjectOf: value].
  		"Word sized integer return"
  		^(atomicType anyMask: 1)
  			ifTrue: [interpreterProxy signedMachineIntegerFor: retVal] "signed return"
  			ifFalse: [interpreterProxy positiveMachineIntegerFor: retVal]]. "unsigned return"
  
+ 	"int64_6, uint64_t"
- 	"longlong, char"
  	(atomicType >> 1) = (FFITypeSignedInt64 >> 1) ifTrue:
  		[^(atomicType anyMask: 1)
  			ifTrue: [interpreterProxy signed64BitIntegerFor: retVal] "signed return"
  			ifFalse: [interpreterProxy positive64BitIntegerFor: retVal]]. "unsigned return"
  
+ 	"char"
  	self assert: (self isCharacterAtomicType: atomicType).
  
  	^atomicType caseOf: {
  		[FFITypeUnsignedChar8]	-> [interpreterProxy characterObjectOf: (retVal bitAnd: 16rFF)].
  		[FFITypeSignedChar8]		-> [interpreterProxy characterObjectOf: (retVal bitAnd: 16rFF)].
  		[FFITypeUnsignedChar16]	-> [interpreterProxy characterObjectOf: (retVal bitAnd: 16rFFFF)].
  		[FFITypeUnsignedChar32]	-> [interpreterProxy characterObjectOf: (self cCoerce: retVal to: #'unsigned int')] }!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiIntegerValueOf: (in category 'callout support') -----
  ffiIntegerValueOf: oop
  	"Support for generic callout. Answer an integer value that is coerced as C would do."
  	<inline: true>
+ 	<returnTypeC: #'usqLong'> "Support up to int64_t or uint64_t, at least intptr_t"
  	"Cheat with a tag test"
  	(oop anyMask: BytesPerWord - 1)
  		ifTrue:
  			[(interpreterProxy isIntegerObject: oop) ifTrue:
  				[^interpreterProxy integerValueOf: oop].
  			self cppIf: SPURVM
  				ifTrue:
  					[(interpreterProxy isCharacterObject: oop) ifTrue: "Immediate in Spur"
  						[^interpreterProxy characterValueOf: oop].
  					 (interpreterProxy isFloatObject: oop) ifTrue: "Immediate in 64-bit Spur"
  						[^interpreterProxy floatValueOf: oop]]]
  		ifFalse:
  			[self cppIf: SPURVM
  				ifTrue: "No non-immediate characters in Spur"
  					[]
  				ifFalse:
  					[(interpreterProxy isCharacterObject: oop) ifTrue:
  						[^interpreterProxy characterValueOf: oop]].
  			 (interpreterProxy isFloatObject: oop) ifTrue:
  				[^interpreterProxy floatValueOf: oop].
  			 oop = interpreterProxy nilObject ifTrue: [^0]. "@@: should we really allow this????"
  			 oop = interpreterProxy falseObject ifTrue: [^0].
  			 oop = interpreterProxy trueObject ifTrue: [^1].
  			 (interpreterProxy isLargePositiveIntegerObject: oop) ifTrue:
+ 				[^interpreterProxy positive64BitValueOf: oop].
+ 			 (interpreterProxy isLargeNegativeIntegerObject: oop) ifTrue:
+ 				[^interpreterProxy signed64BitValueOf: oop]].
- 				[self cppIf: BytesPerWord = 8 "Use cppIf: to get the return type of the function right.  Should be sqInt on 32-bits."
- 					ifTrue: [^interpreterProxy positive64BitValueOf: oop]
- 					ifFalse: [^interpreterProxy positive32BitValueOf: oop]]].
  	^interpreterProxy signedMachineIntegerValueOf: oop "<- will fail if not integer"!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>isFloatAtomicType: (in category 'primitive support') -----
  isFloatAtomicType: atomicTypeCode
  	<inline: true>
+ 	"(atomicTypeCode >> 1) = (FFITypeSingleFloat >> 1)"
+ 	^atomicTypeCode >> 1 = 6 !
- 	^atomicTypeCode >> 1 = 6!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	"Go out, call this guy and create the return value.  This *must* be inlined because of
  	 the alloca of the outgoing stack frame in ffiCall:WithFlags:NumArgs:Args:AndTypes:"
  	| myThreadIndex atomicType floatRet intRet |
  	<var: #floatRet type: #double>
+ 	<var: #intRet type: #usqLong> "Support up to int64_t or uint64_t"
- 	<var: #intRet type: #usqLong>
  	<inline: #always>
  	myThreadIndex := interpreterProxy disownVM: (self disownFlagsFor: calloutState).
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1) ifTrue:
  		[floatRet := self dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)()').
  
  		 "undo any callee argument pops because it may confuse stack management with the alloca."
  		 (self isCalleePopsConvention: calloutState callFlags) ifTrue:
  			[self setsp: calloutState argVector].
  		 interpreterProxy ownVM: myThreadIndex.
  
  		 ^interpreterProxy floatObjectOf: floatRet].
  
  	intRet := self dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqLong (*)()').
  
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  	interpreterProxy ownVM: myThreadIndex.
  
  	(calloutState ffiRetHeader anyMask: FFIFlagPointer+FFIFlagStructure) ifTrue:
  		["Note: Order is important here since FFIFlagPointer + FFIFlagStructure is used to represent
  		 'typedef void* VoidPointer' and VoidPointer must be returned as pointer *not* as struct."
  		 (calloutState ffiRetHeader anyMask: FFIFlagPointer) ifTrue:
  			[^self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^self ffiReturnStruct: (self addressOf: intRet) ofType: (self ffiReturnType: specOnStack) in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSigned32:in: (in category 'marshalling') -----
  ffiPushSigned32: value in: calloutState
+ 	<var: #value type: #sqInt>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: #always>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
+ 	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'signed int').
- 	interpreterProxy longAt: calloutState currentArg put: value.
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushSigned64:in: (in category 'marshalling') -----
  ffiPushSigned64: value in: calloutState
+ 	<var: #value type: #sqLong>
- 	<var: #value type: #usqLong>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: #always>
  	calloutState currentArg + 8 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
  	interpreterProxy
  		longAt: calloutState currentArg put: (self cCoerceSimple: value to: #usqInt);
  		longAt: calloutState currentArg + 4 put: (self cCoerceSimple: value >> 32 to: #usqInt).
  	calloutState currentArg: calloutState currentArg + 8.
  	^0!

Item was changed:
  ----- Method: ThreadedIA32FFIPlugin>>ffiPushUnsigned32:in: (in category 'marshalling') -----
  ffiPushUnsigned32: value in: calloutState
+ 	<var: #value type: #usqInt>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: #always>
  	calloutState currentArg + 4 > calloutState limit ifTrue:
  		[^FFIErrorCallFrameTooBig].
+ 	interpreterProxy longAt: calloutState currentArg put: (self cCoerceSimple: value to: #'unsigned int').
- 	interpreterProxy longAt: calloutState currentArg put: value.
  	calloutState currentArg: calloutState currentArg + 4.
  	^0!



More information about the Vm-dev mailing list