[Vm-dev] VM Maker: VMMaker.oscog-nice.2693.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 1 17:19:52 UTC 2020


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2693.mcz

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

Name: VMMaker.oscog-nice.2693
Author: nice
Time: 1 February 2020, 6:18:54.068162 pm
UUID: 645642cf-46fa-4505-85fb-019e1f91c68e
Ancestors: VMMaker.oscog-eem.2692

Let X64 SysV FFI handle passing/returning union

This can be tricky because we can have union in struct, struct in union etc...
So we must correctly peel the union.

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

Item was changed:
  ----- Method: ThreadedFFIPlugin>>checkAlignmentOfStructSpec:OfLength:StartingAt: (in category 'marshalling-struct') -----
  checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: startIndex
  	"Check the alignment of a structure and return true if correctly aligned.
  	If computed size = declared size, then the struct is assumed correctly aligned."
  	| index spec computedSize fieldAlignment fieldSize declaredSize maxAlignment |
  	<var: #specs type: #'unsigned int*'>
  	<var: #indexPtr type: #'unsigned int*'>
  	<inline: false>
  	index := startIndex.
  	spec := specs at: index.
  	self assert: (spec bitAnd: FFIFlagPointer + FFIFlagAtomic + FFIFlagStructure) = FFIFlagStructure.
+ 	(self isUnionSpec: specs OfLength: specSize StartingAt: index)
+ 		ifTrue:
+ 			[^self checkAlignmentOfUnionSpec: specs OfLength: specSize StartingAt: startIndex].
- 	(self isUnionSpec: specs OfLength: specSize StartingAt: index) ifTrue: [^true].
  	declaredSize := spec bitAnd: FFIStructSizeMask.
  	computedSize := 0.
  	maxAlignment := 1.
  	[index := index + 1.
  	index < specSize]
  		whileTrue:
  			[spec := specs at: index.
  			spec = FFIFlagStructure
  				ifTrue: [^(computedSize - 1 bitOr: maxAlignment - 1) + 1 = declaredSize].
  			(spec anyMask: FFIFlagPointer)
  				ifTrue:
  					[fieldSize := BytesPerWord.
  					fieldAlignment := fieldSize]
  				ifFalse:
  					[fieldSize := spec bitAnd: FFIStructSizeMask.
  					(spec anyMask: FFIFlagStructure)
  						ifTrue:
  							[(self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)
  								ifFalse: [^false].
  							 fieldAlignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: index)]
  						ifFalse: [fieldAlignment := fieldSize]].
  			"round to fieldAlignment"
  			maxAlignment := maxAlignment max: fieldAlignment.
  			computedSize := (computedSize - 1 bitOr: fieldAlignment - 1) + 1.
  			computedSize := computedSize + fieldSize].
  	^(computedSize - 1 bitOr: maxAlignment - 1) + 1 = declaredSize!

Item was added:
+ ----- Method: ThreadedFFIPlugin>>checkAlignmentOfUnionSpec:OfLength:StartingAt: (in category 'marshalling-struct') -----
+ checkAlignmentOfUnionSpec: specs OfLength: specSize StartingAt: startIndex
+ 	"Check the alignment of a union and return true if correctly aligned.
+ 	Union are correctly aligned, but a sub-structure might not."
+ 	| index spec |
+ 	<var: #specs type: #'unsigned int*'>
+ 	<var: #indexPtr type: #'unsigned int*'>
+ 	<inline: false>
+ 	index := startIndex.
+ 	spec := specs at: index.
+ 	[index := index + 1.
+ 	index < specSize]
+ 		whileTrue:
+ 			[spec := specs at: index.
+ 			spec = FFIFlagStructure
+ 				ifTrue: [^true].
+ 			(spec anyMask: FFIFlagPointer)
+ 				ifFalse:
+ 					[(spec anyMask: FFIFlagStructure)
+ 						ifTrue:
+ 							[(self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)
+ 								ifFalse: [^false]]]].
+ 	^true!

Item was added:
+ ----- Method: ThreadedX64SysVFFIPlugin>>registerType:ForStructSpecs:OfLength:StartingAt:ByteOffset:EightbyteOffset: (in category 'marshalling') -----
+ registerType: initialRegisterType ForStructSpecs: specs OfLength: specSize StartingAt: indexPtr ByteOffset: initialByteOffset EightbyteOffset: initialEightbyteOffset
+ 	"Answer with a number characterizing the register type for passing a struct of size <= 16 bytes.
+ 	On input, the index points to the structure header (the one with FFIFlagStructure + structSize)
+ 	On output, the index points to the structure trailer (the FFIFlagStructure)."
+ 
+ 	<var: #specs type: #'unsigned int*'>
+ 	<var: #indexPtr type: #'unsigned int*'>
+ 	<var: #subIndex type: #'unsigned int'>
+ 	<inline: false>
+ 	| registerType eightbyteOffset byteOffset spec fieldSize alignment atomic subIndex isInt recurse subLevel |
+ 	registerType := initialRegisterType.
+ 	byteOffset := initialByteOffset.
+ 	eightbyteOffset := initialEightbyteOffset.
+ 	[indexPtr at: 0 put: (indexPtr at: 0) + 1.
+ 	subLevel := 0.
+ 	(indexPtr at: 0) < specSize]
+ 		whileTrue:
+ 			[spec := specs at: (indexPtr at: 0).
+ 			isInt := false.
+ 			recurse := false.
+ 			spec = FFIFlagStructure "this marks end of structure/union"
+ 				ifTrue:
+ 					[subLevel = 0 ifTrue: [^registerType].
+ 					subLevel := subLevel - 1]
+ 				ifFalse:
+ 					[(spec anyMask: FFIFlagPointer)
+ 						ifTrue:
+ 							[fieldSize := BytesPerWord.
+ 							alignment := fieldSize.
+ 							isInt := true]
+ 						ifFalse:
+ 							[(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
+ 								caseOf:
+ 									{[FFIFlagStructure] ->
+ 										[fieldSize := 0.
+ 										subIndex := indexPtr at: 0.
+ 										alignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: subIndex).
+ 										recurse := self isUnionSpec: specs OfLength: specSize StartingAt: (indexPtr at: 0).
+ 										recurse
+ 											ifTrue: [fieldSize := spec bitAnd: FFIStructSizeMask]
+ 											ifFalse: [subLevel := subLevel + 1]].
+ 									[FFIFlagAtomic] ->
+ 										[fieldSize := spec bitAnd: FFIStructSizeMask.
+ 										alignment := fieldSize.
+ 										atomic := self atomicTypeOf: spec.
+ 										isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
+ 								otherwise: ["invalid spec" ^-1]].
+ 					(byteOffset bitAnd: alignment - 1) = 0
+ 						ifFalse:
+ 							["this field requires alignment"
+ 							byteOffset := (byteOffset bitClear: alignment - 1) + alignment].
+ 					byteOffset + fieldSize > 8
+ 						ifTrue:
+ 							["Not enough room on current Eightbyte for this field, skip to next one"
+ 							eightbyteOffset := eightbyteOffset + 1.
+ 							byteOffset := 0].
+ 					isInt
+ 						ifTrue:
+ 							["If this eightbyte contains an int field, then we must use an int register"
+ 							registerType := registerType bitOr: 1 << eightbyteOffset].
+ 					recurse ifTrue:
+ 						["union in structs require a recursive form, because we handle byteOffset/eightbyteOffset differently"
+ 						registerType := self
+ 								registerType: registerType
+ 								ForUnionSpecs: specs
+ 								OfLength: specSize
+ 								StartingAt: indexPtr
+ 								ByteOffset: byteOffset
+ 								EightbyteOffset: eightbyteOffset].
+ 					"where to put the next field?"
+ 					byteOffset := byteOffset + fieldSize.
+ 					byteOffset >= 8
+ 						ifTrue:
+ 							["This eightbyte is full, skip to next one"
+ 							eightbyteOffset := eightbyteOffset + 1.
+ 							byteOffset := 0]]].
+ 	self assert: subLevel = 0.
+ 	^registerType!

Item was removed:
- ----- Method: ThreadedX64SysVFFIPlugin>>registerType:ForStructSpecs:OfLength:StartingAt:ByteOffset:EightbyteOffset:IsUnion: (in category 'marshalling') -----
- registerType: initialRegisterType ForStructSpecs: specs OfLength: specSize StartingAt: indexPtr ByteOffset: initialByteOffset EightbyteOffset: initialEightbyteOffset IsUnion: isUnion
- 	"Answer with a number characterizing the register type for passing a struct/union of size <= 16 bytes.
- 	The bit at offset i of registerType is set to 1 if eight-byte at offset i is a int register (RAX ...)
- 	The bit at offset 2 indicates if there is a single eightbyte (struct size <= 8)
- 	* 2r00 for float float (XMM0 XMM1)
- 	* 2r01 for int float (RAX XMM0)
- 	* 2r10 for float int (XMM0 RAX)
- 	* 2r11 for int int (RAX RDX)
- 	* 2r100 for float (XMM0)
- 	* 2r101 for int (RAX)
- 	Beware, the bits must be read from right to left for decoding register type.
- 	Note: this method reconstructs the struct layout according to X64 alignment rules.
- 	Therefore, it will not work for packed struct or other exotic alignment.
- 	Note that indexPtr is a pointer so as to be changed on return.
- 	On input, the index points to the structure header (the one with FFIFlagStructure + structSize)
- 	On output, the index points to the structure trailer (the FFIFlagStructure)."
- 
- 	<var: #specs type: #'unsigned int*'>
- 	<var: #indexPtr type: #'unsigned int*'>
- 	<var: #subIndex type: #'unsigned int'>
- 	| registerType eightbyteOffset byteOffset spec fieldSize alignment atomic subIndex isInt recurse subLevel |
- 	registerType := initialRegisterType.
- 	byteOffset := initialByteOffset.
- 	eightbyteOffset := initialEightbyteOffset.
- 	[indexPtr at: 0 put: (indexPtr at: 0) + 1.
- 	subLevel := 0.
- 	(indexPtr at: 0) < specSize]
- 		whileTrue:
- 			[spec := specs at: (indexPtr at: 0).
- 			isInt := false.
- 			recurse := false.
- 			spec = FFIFlagStructure "this marks end of structure/union"
- 				ifTrue:
- 					[subLevel = 0 ifTrue: [^registerType].
- 					subLevel := subLevel - 1]
- 				ifFalse:
- 					[(spec anyMask: FFIFlagPointer)
- 						ifTrue:
- 							[fieldSize := BytesPerWord.
- 							alignment := fieldSize.
- 							isInt := true]
- 						ifFalse:
- 							[(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
- 								caseOf:
- 									{[FFIFlagStructure] ->
- 										[fieldSize := 0.
- 										subIndex := indexPtr at: 0.
- 										alignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: subIndex).
- 										recurse := (self isUnionSpec: specs OfLength: specSize StartingAt: (indexPtr at: 0)) ~= isUnion.
- 										recurse ifFalse: [subLevel := subLevel + 1]].
- 									[FFIFlagAtomic] ->
- 										[fieldSize := spec bitAnd: FFIStructSizeMask.
- 										alignment := fieldSize.
- 										atomic := self atomicTypeOf: spec.
- 										isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
- 								otherwise: ["invalid spec" ^-1]].
- 					(byteOffset bitAnd: alignment - 1) = 0
- 						ifFalse:
- 							["this field requires alignment"
- 							self assert: isUnion not.
- 							byteOffset := (byteOffset bitClear: alignment - 1) + alignment].
- 					byteOffset + fieldSize > 8
- 						ifTrue:
- 							["Not enough room on current Eightbyte for this field, skip to next one"
- 							self assert: isUnion not.
- 							eightbyteOffset := eightbyteOffset + 1.
- 							byteOffset := 0].
- 					isInt
- 						ifTrue:
- 							["If this eightbyte contains an int field, then we must use an int register"
- 							registerType := registerType bitOr: 1 << eightbyteOffset].
- 					recurse ifTrue:
- 						["struct in union and union in structs require a recursive form, because we handle byteOffset/eightbyteOffset differently"
- 						registerType := self
- 								registerType: registerType
- 								ForStructSpecs: specs
- 								OfLength: specSize
- 								StartingAt: indexPtr
- 								ByteOffset: byteOffset
- 								EightbyteOffset: eightbyteOffset
- 								IsUnion: isUnion not].
- 					isUnion
- 						ifFalse:
- 							["where to put the next field?"
- 							byteOffset := byteOffset + fieldSize.
- 							byteOffset >= 8
- 								ifTrue:
- 									["This eightbyte is full, skip to next one"
- 									eightbyteOffset := eightbyteOffset + 1.
- 									byteOffset := 0]]]].
- 	self assert: false. "should not reach here"
- 	^-1!

Item was added:
+ ----- Method: ThreadedX64SysVFFIPlugin>>registerType:ForUnionSpecs:OfLength:StartingAt:ByteOffset:EightbyteOffset: (in category 'marshalling') -----
+ registerType: initialRegisterType ForUnionSpecs: specs OfLength: specSize StartingAt: indexPtr ByteOffset: byteOffset EightbyteOffset: eightbyteOffset
+ 	"Answer with a number characterizing the register type for passing a union of size <= 16 bytes.
+ 	On input, the index points to the structure header (the one with FFIFlagStructure + structSize)
+ 	On output, the index points to the structure trailer (the FFIFlagStructure)."
+ 
+ 	<var: #specs type: #'unsigned int*'>
+ 	<var: #indexPtr type: #'unsigned int*'>
+ 	<var: #subIndex type: #'unsigned int'>
+ 	<inline: false>
+ 	| registerType spec atomic isInt recurse subLevel |
+ 	registerType := initialRegisterType.
+ 	[indexPtr at: 0 put: (indexPtr at: 0) + 1.
+ 	subLevel := 0.
+ 	(indexPtr at: 0) < specSize]
+ 		whileTrue:
+ 			[spec := specs at: (indexPtr at: 0).
+ 			isInt := false.
+ 			recurse := false.
+ 			spec = FFIFlagStructure "this marks end of structure/union"
+ 				ifTrue:
+ 					[subLevel = 0 ifTrue: [^registerType].
+ 					subLevel := subLevel - 1]
+ 				ifFalse:
+ 					[(spec anyMask: FFIFlagPointer)
+ 						ifTrue:
+ 							[isInt := true]
+ 						ifFalse:
+ 							[(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
+ 								caseOf:
+ 									{[FFIFlagStructure] ->
+ 										[recurse := (self isUnionSpec: specs OfLength: specSize StartingAt: (indexPtr at: 0))not.
+ 										recurse ifFalse: [subLevel := subLevel + 1]].
+ 									[FFIFlagAtomic] ->
+ 										[atomic := self atomicTypeOf: spec.
+ 										isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
+ 								otherwise: ["invalid spec" ^-1]].
+ 					isInt
+ 						ifTrue:
+ 							["If this eightbyte contains an int field, then we must use an int register"
+ 							registerType := registerType bitOr: 1 << eightbyteOffset].
+ 					recurse ifTrue:
+ 						["struct in union require a recursive form, because we handle byteOffset/eightbyteOffset differently"
+ 						registerType := self
+ 								registerType: registerType
+ 								ForStructSpecs: specs
+ 								OfLength: specSize
+ 								StartingAt: indexPtr
+ 								ByteOffset: byteOffset
+ 								EightbyteOffset: eightbyteOffset]]].
+ 	self assert: subLevel = 0.
+ 	^registerType!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>registerTypeForStructSpecs:OfLength: (in category 'marshalling') -----
  registerTypeForStructSpecs: specs OfLength: specSize
  	"Answer with a number characterizing the register type for passing a struct of size <= 16 bytes.
  	The bit at offset i of registerType is set to 1 if eightbyte at offset i is a int register (RAX ...)
  	The bit at offset 2 indicates if there is a single eightbyte (struct size <= 8)
  	* 2r00 for float float (XMM0 XMM1)
  	* 2r01 for int float (RAX XMM0)
  	* 2r10 for float int (XMM0 RAX)
  	* 2r11 for int int (RAX RDX)
  	* 2r100 for float (XMM0)
  	* 2r101 for int (RAX)
  	* 2r110 INVALID (not aligned)
  	Beware, the bits must be read from right to left for decoding register type.
  	Note: this method reconstructs the struct layout according to X64 alignment rules.
  	Therefore, it will not work for packed struct or other exotic alignment."
  
  	<var: #specs type: #'unsigned int*'>
  	<var: #subIndex type: #'unsigned int'>
  	<inline: false>
+ 	| index byteSize registerType |
- 	| eightByteOffset byteOffset index registerType spec fieldSize alignment atomic subIndex isInt |
  	index := 0.
+ 	byteSize := (specs at: index) bitAnd: FFIStructSizeMask.
+ 	byteSize > 16 ifTrue: [^2r110].
  	(self checkAlignmentOfStructSpec: specs OfLength: specSize StartingAt: index)
  		ifFalse: [^2r110].
+ 	registerType := byteSize <= 8 ifTrue: [2r100] ifFalse: [0].
+ 	^(self isUnionSpec: specs OfLength: specSize StartingAt: 0)
+ 		ifTrue: [ self 
+ 			registerType: registerType
+ 			ForUnionSpecs: specs
+ 			OfLength: specSize
+ 			StartingAt: (self addressOf: index)
+ 			ByteOffset: 0
+ 			EightbyteOffset: 0 ]
+ 		ifFalse: [ self 
+ 			registerType: registerType
+ 			ForStructSpecs: specs
+ 			OfLength: specSize
+ 			StartingAt: (self addressOf: index)
+ 			ByteOffset: 0
+ 			EightbyteOffset: 0 ]!
- 	eightByteOffset := 0.
- 	byteOffset := 0.
- 	registerType := ((specs at: index) bitAnd: FFIStructSizeMask) <= 8 ifTrue: [2r100] ifFalse: [0].
- 	[(index := index + 1) < specSize]
- 		whileTrue:
- 			[spec := specs at: index.
- 			isInt := false.
- 			spec = FFIFlagStructure "this marks end of structure and should be ignored"
- 				ifFalse:
- 					[(spec anyMask: FFIFlagPointer)
- 						ifTrue:
- 							[fieldSize := BytesPerWord.
- 							alignment := fieldSize.
- 							isInt := true]
- 						ifFalse:
- 							[(spec bitAnd: FFIFlagStructure + FFIFlagAtomic)
- 								caseOf:
- 									{[FFIFlagStructure] ->
- 										[fieldSize := 0.
- 										subIndex := index.
- 										alignment := self alignmentOfStructSpec: specs OfLength: specSize StartingAt: (self addressOf: subIndex)].
- 									[FFIFlagAtomic] ->
- 										[fieldSize := spec bitAnd: FFIStructSizeMask.
- 										alignment := fieldSize.
- 										atomic := self atomicTypeOf: spec.
- 										isInt := (atomic >> 1) ~= (FFITypeSingleFloat >> 1)]}
- 								otherwise: ["invalid spec" ^-1]].
- 					(byteOffset bitAnd: alignment - 1) = 0
- 						ifFalse:
- 							["this field requires alignment"
- 							byteOffset := (byteOffset bitClear: alignment - 1) + alignment].
- 					byteOffset + fieldSize > 8
- 						ifTrue:
- 							["Not enough room on current eightbyte for this field, skip to next one"
- 							eightByteOffset := eightByteOffset + 1.
- 							byteOffset := 0].
- 					isInt
- 						ifTrue:
- 							["If this eightbyte contains an int field, then we must use an int register"
- 							registerType := registerType bitOr: 1 << eightByteOffset].
- 					"where to put the next field?"
- 					byteOffset := byteOffset + fieldSize.
- 					byteOffset >= 8
- 						ifTrue:
- 							["This eightbyte is full, skip to next one"
- 							eightByteOffset := eightByteOffset + 1.
- 							byteOffset := 0]]].
- 	^registerType!



More information about the Vm-dev mailing list