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

commits at source.squeak.org commits at source.squeak.org
Mon Aug 16 07:14:19 UTC 2021


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

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

Name: VMMaker.oscog-mt.3039
Author: mt
Time: 16 August 2021, 9:14:03.822631 am
UUID: b082e313-a708-7f47-a7fd-5d96cb87a2df
Ancestors: VMMaker.oscog-eem.3038

Complements FFI-Pools-mt.33

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

Item was changed:
  ----- Method: FFIPlugin>>ffiArgByValue: (in category 'callout support') -----
  ffiArgByValue: oop
  	"Support for generic callout. Prepare an argument by value for a callout."
  	| atomicType intValue floatValue |
  	<inline: true>
  	<var: #floatValue type: 'double'>
  	atomicType := self atomicTypeOf: ffiArgHeader.
  	"check if the range is valid"
  	(atomicType < 0 or:[atomicType > FFITypeDoubleFloat])
  		ifTrue:[^self ffiFail: FFIErrorBadAtomicType].
  	atomicType < FFITypeSingleFloat ifTrue:["integer types"
+ 		(atomicType >> 1) = (FFITypeSignedInt64 >> 1)
- 		(atomicType >> 1) = (FFITypeSignedLongLong >> 1)
  			ifTrue:[intValue := oop] "ffi support code must coerce longlong"
  			ifFalse:[intValue := self ffiIntegerValueOf: oop]. "does all the coercions"
  		interpreterProxy failed ifTrue:[^self ffiFail: FFIErrorCoercionFailed].
  		self dispatchOn: atomicType
  			in: #(
  				ffiPushVoid:
  				ffiPushUnsignedInt:
  				ffiPushUnsignedByte:
  				ffiPushSignedByte:
  				ffiPushUnsignedShort:
  				ffiPushSignedShort:
  				ffiPushUnsignedInt:
  				ffiPushSignedInt:
  				ffiPushUnsignedLongLongOop:
  				ffiPushSignedLongLongOop:
  				ffiPushUnsignedChar:
  				ffiPushSignedChar:)
  		with: intValue.
  	] ifFalse:[
  		"either float or double"
  		floatValue := self ffiFloatValueOf: oop.
  		interpreterProxy failed ifTrue:[^self ffiFail: FFIErrorCoercionFailed].
  		atomicType = FFITypeSingleFloat
  			ifTrue:[self ffiPushSingleFloat: floatValue]
  			ifFalse:[self ffiPushDoubleFloat: floatValue].
  	].
  	^0!

Item was changed:
  ----- Method: FFIPlugin>>ffiAtomicArgByReference:Class: (in category 'callout support') -----
  ffiAtomicArgByReference: oop Class: oopClass
  	"Support for generic callout. Prepare a pointer reference to an atomic type for callout. Note: for type 'void*' we allow either one of ByteArray/String/Symbol or wordVariableSubclass."
  	| atomicType isString |
  	<inline: true>
  	atomicType := self atomicTypeOf: ffiArgHeader.
  	(atomicType = FFITypeBool) "No bools on input"
  		ifTrue:[^self ffiFail: FFIErrorCoercionFailed].
  	((atomicType >> 1) = (FFITypeSignedChar >> 1)) ifTrue:["string value (char*)"
  		"note: the only types allowed for passing into char* types are
  		ByteArray, String, Symbol and *no* other byte indexed objects
  		(e.g., CompiledMethod, LargeInteger). We only check for strings
  		here and fall through to the byte* check otherwise."
  		isString := interpreterProxy 
  					includesBehavior: oopClass 
  					ThatOf: interpreterProxy classString.
  		isString ifTrue:["String/Symbol"
  			"Strings must be allocated by the ffi support code"
  			^self ffiPushString: (self cCoerce: (interpreterProxy firstIndexableField: oop) to: 'int') OfLength: (interpreterProxy byteSizeOf: oop)].
  		"Fall through to byte* test"
+ 		atomicType := FFITypeUnsignedInt8].
- 		atomicType := FFITypeUnsignedByte].
  
+ 	(atomicType = FFITypeVoid or:[(atomicType >> 1) = (FFITypeSignedInt8 >> 1)]) ifTrue:[
- 	(atomicType = FFITypeVoid or:[(atomicType >> 1) = (FFITypeSignedByte >> 1)]) ifTrue:[
  		"byte* -- see comment on string above"
  		oopClass = interpreterProxy classByteArray ifTrue:["ByteArray"
  			^self ffiPushPointer: (self cCoerce: (interpreterProxy firstIndexableField: oop) to:'int')].
  		isString := interpreterProxy includesBehavior: oopClass 
  					ThatOf: interpreterProxy classString.
  		isString ifTrue:["String/Symbol"
  			^self ffiPushPointer: (self cCoerce: (interpreterProxy firstIndexableField: oop) to:'int')].
  		atomicType = FFITypeVoid ifFalse:[^self ffiFail: FFIErrorCoercionFailed].
  		"note: type void falls through"
  	].
  
+ 	(atomicType <= FFITypeSignedInt32 "void/short/int"
- 	(atomicType <= FFITypeSignedInt "void/short/int"
  		or:[atomicType = FFITypeSingleFloat]) ifTrue:[
  			"require a word subclass to work"
  			(interpreterProxy isWords: oop) ifTrue:[
  				^self ffiPushPointer: (self cCoerce: (interpreterProxy firstIndexableField: oop) to:'int')]].
  
  	^self ffiFail: FFIErrorCoercionFailed.!

Item was changed:
  ----- Method: FFIPlugin>>ffiCreateReturnOop: (in category 'callout support') -----
  ffiCreateReturnOop: retVal
  	"Callout support. Return the appropriate oop for the given atomic value"
  	| atomicType shift value mask byteSize |
  	atomicType := self atomicTypeOf: ffiRetHeader.
  	atomicType = FFITypeBool ifTrue:[
  			"Make sure bool honors the byte size requested"
  			byteSize := ffiRetHeader bitAnd: FFIStructSizeMask.
  			byteSize = 4
  				ifTrue:[value := retVal]
  				ifFalse:[value := retVal bitAnd: 1 << (byteSize * 8) - 1].
  			value = 0
  				ifTrue:[^interpreterProxy falseObject]
  				ifFalse:[^interpreterProxy trueObject]].
+ 	atomicType <= FFITypeSignedInt32 ifTrue:[
- 	atomicType <= FFITypeSignedInt ifTrue:[
  		"these are all generall integer returns"
+ 		atomicType <= FFITypeSignedInt16 ifTrue:[
- 		atomicType <= FFITypeSignedShort ifTrue:[
  			"byte/short. first extract partial word, then sign extend"
  			shift := (atomicType >> 1) * 8. "# of significant bits"
  			value := retVal bitAnd: (1 << shift - 1). 
  			(atomicType anyMask: 1) ifTrue:[
  				"make the guy signed"
  				mask := 1 << (shift-1).
  				value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  			^interpreterProxy integerObjectOf: value].
  		"32bit integer return"
  		(atomicType anyMask: 1)
  			ifTrue:[^(interpreterProxy signed32BitIntegerFor: retVal)] "signed return"
  			ifFalse:[^(interpreterProxy positive32BitIntegerFor: retVal)]]. "unsigned return"
  
  	atomicType < FFITypeSingleFloat ifTrue:[
  		"longlong, char"
+ 		(atomicType >> 1) = (FFITypeSignedInt64 >> 1) 
- 		(atomicType >> 1) = (FFITypeSignedLongLong >> 1) 
  			ifTrue:[^self ffiCreateLongLongReturn: (atomicType anyMask: 1)]
  			ifFalse:[^(interpreterProxy 
  						fetchPointer: (retVal bitAnd: 255)
  						ofObject: interpreterProxy characterTable)]].
  	"float return"
  	^interpreterProxy floatObjectOf: (self ffiReturnFloatValue).!

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: #floatValue type: #double>
  	atomicType := self atomicTypeOf: calloutState ffiArgHeader.
  	"check if the range is valid"
  	(atomicType < 0 or:[atomicType > FFITypeDoubleFloat])
  		ifTrue:[^FFIErrorBadAtomicType].
  	atomicType < FFITypeSingleFloat ifTrue:["integer types"
+ 		(atomicType >> 1) = (FFITypeSignedInt64 >> 1)
- 		(atomicType >> 1) = (FFITypeSignedLongLong >> 1)
  			ifTrue:[intValue := oop] "ffi support code must coerce longlong"
  			ifFalse:[intValue := self ffiIntegerValueOf: oop]. "does all the coercions"
  		interpreterProxy failed ifTrue:[^FFIErrorCoercionFailed].
  		^self dispatchOn: atomicType
  			in: #(
  				ffiPushVoid:in:
  				ffiPushUnsignedInt:in:
  				ffiPushUnsignedByte:in:
  				ffiPushSignedByte:in:
  				ffiPushUnsignedShort:in:
  				ffiPushSignedShort:in:
  				ffiPushUnsignedInt:in:
  				ffiPushSignedInt:in:
  				ffiPushUnsignedLongLongOop:in:
  				ffiPushSignedLongLongOop:in:
  				ffiPushUnsignedChar:in:
  				ffiPushSignedChar:in:)
  			with: intValue
  			with: calloutState].
  	"either float or double"
  	floatValue := self ffiFloatValueOf: oop.
  	interpreterProxy failed ifTrue:
  		[^FFIErrorCoercionFailed].
  	atomicType = FFITypeSingleFloat
  		ifTrue: [^self ffiPushSingleFloat: floatValue in: calloutState]
  		ifFalse:[^self ffiPushDoubleFloat: floatValue in: calloutState]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiAtomicArgByReference:Class:in: (in category 'callout support') -----
  ffiAtomicArgByReference: oop Class: oopClass in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Support for generic callout. Prepare a pointer reference to an atomic type for callout.
  	 Note: 
  		for type 'void*' we allow ByteArray/String/Symbol, wordVariableSubclass, Alien or ExternalAddress.
  		for other types we allow ByteArray, wordVariableSubclass, Alien or ExternalAddress."
  	| atomicType isString argIsAlien |
  	<inline: #always>
  	atomicType := self atomicTypeOf: calloutState ffiArgHeader.
  	(atomicType = FFITypeBool) ifTrue: "No bools on input"
  		[^FFIErrorCoercionFailed].
  	argIsAlien := (isString := interpreterProxy 
  								includesBehavior: oopClass 
  								ThatOf: interpreterProxy classString)
  					ifTrue: [false]
  					ifFalse:
  						[interpreterProxy 
  							includesBehavior: oopClass 
  							ThatOf: interpreterProxy classAlien].
  	((atomicType >> 1) = (FFITypeSignedChar >> 1)) ifTrue:"string value (char*)"
  		"note: the only types allowed for passing into char* types are
  		ByteArray, String, Symbol, Alien and *no* other byte indexed objects
  		(e.g., CompiledMethod, LargeInteger). We only check for strings
  		here and fall through to the byte* check otherwise."
  		[isString ifTrue:"String/Symbol"
  			"Strings must be allocated by the ffi support code"
  			[^self ffiPushString: (interpreterProxy firstIndexableField: oop)
  				OfLength: (interpreterProxy byteSizeOf: oop)
  				in: calloutState].
  		"Fall through to byte* test"
+ 		atomicType := FFITypeUnsignedInt8].
- 		atomicType := FFITypeUnsignedByte].
  
  	self cppIf: COGMTVM ifTrue:
  	["Since all the following pass the address of the first indexable field we need to fail
  	 the call if it is threaded and the object is young, since it may move during the call."
  	((calloutState callFlags anyMask: FFICallFlagThreaded)
  	and: [(argIsAlien not or: [self isDirectAlien: oop])
  	and: [interpreterProxy isYoung: oop]]) ifTrue:
  		[^PrimErrObjectMayMove negated]].
  
+ 	(atomicType = FFITypeVoid or:[(atomicType >> 1) = (FFITypeSignedInt8 >> 1)]) ifTrue:
- 	(atomicType = FFITypeVoid or:[(atomicType >> 1) = (FFITypeSignedByte >> 1)]) ifTrue:
  		"byte* -- see comment on string above"
  		[(isString or: [oopClass = interpreterProxy classByteArray]) ifTrue: "String/Symbol/ByteArray"
  			[^self ffiPushPointer: (interpreterProxy firstIndexableField: oop) in: calloutState].
  		(oopClass = interpreterProxy classExternalAddress) ifTrue: 
  			[^self ffiPushPointer: (self longAt: oop + interpreterProxy baseHeaderSize) in: calloutState].
  		argIsAlien ifTrue:
  			[^self ffiPushPointer: (self pointerForOop: (self startOfData: oop)) in: calloutState].
  		atomicType = FFITypeVoid ifFalse:
  			[^FFIErrorCoercionFailed]].
  		"note: type void falls through"
  
  	"I can push pointers to any type (take for instance calls who receive int* output arguments, etc.)
  	 but I need to store them into a ByteArray, ExternalAddress or Alien"
  	(atomicType <= FFITypeDoubleFloat) ifTrue:
  		[((interpreterProxy isWords: oop) or: [oopClass = interpreterProxy classByteArray]) ifTrue:
  			[^self ffiPushPointer: (interpreterProxy firstIndexableField: oop) in: calloutState].
  		(oopClass = interpreterProxy classExternalAddress) ifTrue: 
  			[^self ffiPushPointer: (self longAt: oop + interpreterProxy baseHeaderSize) in: calloutState].
  		argIsAlien ifTrue:
  			[^self ffiPushPointer: (self pointerForOop: (self startOfData: oop)) in: calloutState]].
  
  	^FFIErrorCoercionFailed!

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>
  	"Callout support. Return the appropriate oop for the given atomic type"
  	| shift value mask byteSize |
  	<var: 'value' type: #usqLong>
  	<var: 'mask' type: #usqLong>
  	self assert: atomicType < FFITypeSingleFloat.
  
  	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:
- 	atomicType <= FFITypeSignedInt ifTrue:
  		["these are all generall integer returns"
+ 		atomicType <= (BytesPerWord = 8 ifTrue: [FFITypeSignedInt32] ifFalse: [FFITypeSignedInt16]) ifTrue:
- 		atomicType <= (BytesPerWord = 8 ifTrue: [FFITypeSignedInt] ifFalse: [FFITypeSignedShort]) ifTrue:
  			["byte/short. first extract partial word, then sign extend"
+ 			shift := (BytesPerWord = 8 and: [atomicType >= FFITypeUnsignedInt32])
- 			shift := (BytesPerWord = 8 and: [atomicType >= FFITypeUnsignedInt])
  						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"
  
  	"longlong, char"
+ 	(atomicType >> 1) = (FFITypeSignedInt64 >> 1) ifTrue:
- 	(atomicType >> 1) = (FFITypeSignedLongLong >> 1) ifTrue:
  		[^(atomicType anyMask: 1)
  			ifTrue: [interpreterProxy signed64BitIntegerFor: retVal] "signed return"
  			ifFalse: [interpreterProxy positive64BitIntegerFor: retVal]].
  	self flag: 'we need a solution for wide characters; spur supports upto 30 bit characters'.
  	^interpreterProxy characterObjectOf: (retVal bitAnd: 16rFF)!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiValidateExternalData:AtomicType: (in category 'callout support') -----
  ffiValidateExternalData: oop AtomicType: atomicType
  	"Validate if the given oop (an instance of ExternalData) can be passed as a pointer to the given atomic type."
  	| ptrType specOop spec specType |
  	<inline: true>
  	ptrType := interpreterProxy fetchPointer: 1 ofObject: oop.
  	((interpreterProxy isPointers: ptrType)
  	and: [(interpreterProxy slotSizeOf: ptrType) >= 2]) ifFalse:
  		[^FFIErrorWrongType].
  	specOop := interpreterProxy fetchPointer: 0 ofObject: ptrType.
  	((interpreterProxy isWords: specOop)
  	and: [(interpreterProxy slotSizeOf: specOop) > 0]) ifFalse:
  		[^FFIErrorWrongType].
  	spec := interpreterProxy fetchPointer: 0 ofObject: specOop.
  	(self isAtomicType: spec) ifFalse:
  		[^FFIErrorWrongType].
  	specType := self atomicTypeOf: spec.
  	specType ~= atomicType ifTrue:
  		"Allow for signed/unsigned conversion but nothing else.
  		 See FFIConstants class>>#initializeTypeConstants"
+ 		[(atomicType >= FFITypeUnsignedInt8
- 		[(atomicType >= FFITypeUnsignedByte
  		  and: [atomicType <= FFITypeSignedChar
  		  and: [(atomicType >> 1) = (specType >> 1)]]) ifFalse:
  			[^FFIErrorCoercionFailed]].
  	^0!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveStructureElementAlignment (in category 'primitives') -----
  primitiveStructureElementAlignment
  	"Answer the alignment of an element of an atomic type, or a structure, within a structure on the current platform."
  	<export: true flags: #FastCPrimitiveFlag>
  	| typeCode alignment |
  	<var: 'alignment' type: #'void *'>
  	typeCode := interpreterProxy stackValue: 0.
  	((interpreterProxy isIntegerObject: typeCode)
+ 	 and: [((typeCode := interpreterProxy integerValueOf: typeCode) between: FFITypeUnsignedInt8 and: FFITypeDoubleFloat)
- 	 and: [((typeCode := interpreterProxy integerValueOf: typeCode) between: FFITypeUnsignedByte and: FFITypeDoubleFloat)
  		or: [typeCode = FFIFlagStructure]]) ifFalse:
  		[^self primitiveFailFor: PrimErrBadArgument].
  
  	alignment := typeCode
  					caseOf: {
+ 						[FFITypeUnsignedInt8]			-> [self structOffsetOf: 'structByte *' atomicTypeCode: FFITypeUnsignedInt8].
+ 						[FFITypeSignedInt8]			-> [self structOffsetOf: 'structByte *' atomicTypeCode: FFITypeSignedInt8].
+ 						[FFITypeUnsignedInt16]		-> [self structOffsetOf: 'structShort *' atomicTypeCode: FFITypeUnsignedInt16].
+ 						[FFITypeSignedInt16]			-> [self structOffsetOf: 'structShort *' atomicTypeCode: FFITypeSignedInt16].
+ 						[FFITypeUnsignedInt32]			-> [self structOffsetOf: 'structInt *' atomicTypeCode: FFITypeUnsignedInt32].
+ 						[FFITypeSignedInt32]				-> [self structOffsetOf: 'structInt *' atomicTypeCode: FFITypeSignedInt32].
+ 						[FFITypeUnsignedInt64]	-> [self structOffsetOf: 'structLongLong *' atomicTypeCode: FFITypeUnsignedInt64].
+ 						[FFITypeSignedInt64]		-> [self structOffsetOf: 'structLongLong *' atomicTypeCode: FFITypeSignedInt64].
- 						[FFITypeUnsignedByte]			-> [self structOffsetOf: 'structByte *' atomicTypeCode: FFITypeUnsignedByte].
- 						[FFITypeSignedByte]			-> [self structOffsetOf: 'structByte *' atomicTypeCode: FFITypeUnsignedByte].
- 						[FFITypeUnsignedShort]		-> [self structOffsetOf: 'structShort *' atomicTypeCode: FFITypeUnsignedShort].
- 						[FFITypeSignedShort]			-> [self structOffsetOf: 'structShort *' atomicTypeCode: FFITypeUnsignedShort].
- 						[FFITypeUnsignedInt]			-> [self structOffsetOf: 'structInt *' atomicTypeCode: FFITypeUnsignedInt].
- 						[FFITypeSignedInt]				-> [self structOffsetOf: 'structInt *' atomicTypeCode: FFITypeUnsignedInt].
- 						[FFITypeUnsignedLongLong]	-> [self structOffsetOf: 'structLongLong *' atomicTypeCode: FFITypeUnsignedLongLong].
- 						[FFITypeSignedLongLong]		-> [self structOffsetOf: 'structLongLong *' atomicTypeCode: FFITypeUnsignedLongLong].
  						[FFITypeSingleFloat]			-> [self structOffsetOf: 'structFloat *' atomicTypeCode: FFITypeSingleFloat].
  						[FFITypeDoubleFloat]			-> [self structOffsetOf: 'structDouble *' atomicTypeCode: FFITypeDoubleFloat].
  					}
  					otherwise: [self structOffsetOf: 'structStruct *' atomicTypeCode: FFIFlagStructure].
  	^interpreterProxy methodReturnInteger: alignment asUnsignedIntegerPtr!



More information about the Vm-dev mailing list