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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 13 15:45:59 UTC 2016


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

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

Name: VMMaker.oscog-nice.1990
Author: nice
Time: 13 November 2016, 4:43:50.332281 pm
UUID: c6fc0dfe-e6b3-4eff-bd4c-ed591f81125e
Ancestors: VMMaker.oscog-nice.1989

Fix passing 64bits args thru LLP64 FFI.

=============== Diff against VMMaker.oscog-nice.1989 ===============

Item was changed:
  ----- Method: ThreadedARMFFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double, double, double, double, double)'>
  	"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 loadFloatRegs oop |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
  	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[myThreadIndex := interpreterProxy disownVM: 0]].
  
  	self registerArgsSlop + self cStackAlignment > 0 ifTrue:
  		[self setsp: calloutState argVector].
  
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self 
  			load: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 0)) to: 'double *') at: 0)
  			Flo: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 2)) to: 'double *') at: 0)
  			a: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 4)) to: 'double *') at: 0)
  			t: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 6)) to: 'double *') at: 0)
  			R: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 8)) to: 'double *') at: 0)
  			e: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 10)) to: 'double *') at: 0)
  			g: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 12)) to: 'double *') at: 0)
  			s: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 14)) to: 'double *') at: 0)].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[atomicType = FFITypeSingleFloat
  				ifTrue:
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]
  				ifFalse: "atomicType = FFITypeDoubleFloat"
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]]
  		ifFalse:
  			[intRet := self 
+ 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqLong (*)(long, long, long, long)') 
  				with: (calloutState integerRegisters at: 0)
  				with: (calloutState integerRegisters at: 1)
  				with: (calloutState integerRegisters at: 2)
  				with: (calloutState integerRegisters at: 3)].
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[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:
  				[oop := self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
  			ifFalse:
  				[oop := self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^oop].
  	
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[oop := interpreterProxy floatObjectOf: floatRet]
  		ifFalse:
  			[oop := self ffiCreateIntegralResultOop: intRet
  						ofAtomicType: atomicType
  						in: calloutState].
  	^interpreterProxy methodReturnValue: oop!

Item was changed:
  ----- Method: ThreadedX64SysVFFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double, double, double, double, double)'>
  	"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 loadFloatRegs oop |
  	<var: #floatRet type: #double>
  	<var: #intRet type: 'SixteenByteReturn'>
  	<inline: true>
  	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[myThreadIndex := interpreterProxy disownVM: 0]].
  
  	self registerArgsSlop + self cStackAlignment > 0 ifTrue:
  		[self setsp: calloutState argVector].
  
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self 
  			load: (calloutState floatRegisters at: 0)
  			Flo: (calloutState floatRegisters at: 1)
  			a: (calloutState floatRegisters at: 2)
  			t: (calloutState floatRegisters at: 3)
  			R: (calloutState floatRegisters at: 4)
  			e: (calloutState floatRegisters at: 5)
  			g: (calloutState floatRegisters at: 6)
  			s: (calloutState floatRegisters at: 7)].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[atomicType = FFITypeSingleFloat
  				ifTrue:
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(long, long, long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)
  						with: (calloutState integerRegisters at: 4)
  						with: (calloutState integerRegisters at: 5)]
  				ifFalse: "atomicType = FFITypeDoubleFloat"
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(long, long, long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)
  						with: (calloutState integerRegisters at: 4)
  						with: (calloutState integerRegisters at: 5)]]
  		ifFalse:
  			[intRet := self 
+ 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturn (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'SixteenByteReturn (*)(long, long, long, long, long, long)') 
  				with: (calloutState integerRegisters at: 0)
  				with: (calloutState integerRegisters at: 1)
  				with: (calloutState integerRegisters at: 2)
  				with: (calloutState integerRegisters at: 3)
  				with: (calloutState integerRegisters at: 4)
  				with: (calloutState integerRegisters at: 5)].
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[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:
  				[oop := self ffiReturnPointer: intRet a ofType: (self ffiReturnType: specOnStack) in: calloutState]
  			ifFalse:
  				[oop := self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^oop].
  	
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[oop := interpreterProxy floatObjectOf: floatRet]
  		ifFalse:
  			[oop := self ffiCreateIntegralResultOop: intRet a
  						ofAtomicType: atomicType
  						in: calloutState].
  	^interpreterProxy methodReturnValue: oop!

Item was changed:
  ----- Method: ThreadedX64Win64FFIPlugin>>ffiCalloutTo:SpecOnStack:in: (in category 'callout support') -----
  ffiCalloutTo: procAddr SpecOnStack: specOnStack in: calloutState
  	<var: #procAddr type: #'void *'>
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #loadFloatRegs declareC: 'extern void loadFloatRegs(double, double, double, double)'>
  	"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 loadFloatRegs oop |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
  	self cCode: '' inSmalltalk: [loadFloatRegs := #used. loadFloatRegs class].
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[myThreadIndex := interpreterProxy disownVM: 0]].
  
  	self registerArgsSlop + self cStackAlignment > 0 ifTrue:
  		[self setsp: calloutState argVector].
  
  	calloutState floatRegisterSignature > 0 ifTrue:
  		[self 
  			load: (calloutState floatRegisters at: 0)
  			Flo: (calloutState floatRegisters at: 1)
  			at: (calloutState floatRegisters at: 2)
  			Re: (calloutState floatRegisters at: 3)
  			gs: (calloutState floatRegisters at: 4)].
  
  	atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[atomicType = FFITypeSingleFloat
  				ifTrue:
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'float (*)(long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]
  				ifFalse: "atomicType = FFITypeDoubleFloat"
  					[floatRet := self 
+ 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 						dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(long, long, long, long)') 
  						with: (calloutState integerRegisters at: 0)
  						with: (calloutState integerRegisters at: 1)
  						with: (calloutState integerRegisters at: 2)
  						with: (calloutState integerRegisters at: 3)]]
  		ifFalse:
  			[intRet := self 
+ 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)') 
- 				dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'usqLong (*)(long, long, long, long)') 
  				with: (calloutState integerRegisters at: 0)
  				with: (calloutState integerRegisters at: 1)
  				with: (calloutState integerRegisters at: 2)
  				with: (calloutState integerRegisters at: 3)].
  	"undo any callee argument pops because it may confuse stack management with the alloca."
  	(self isCalleePopsConvention: calloutState callFlags) ifTrue:
  		[self setsp: calloutState argVector].
  
  	self cppIf: COGMTVM ifTrue:
  	[(calloutState callFlags anyMask: FFICallFlagThreaded) ifTrue:
  		[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:
  				[oop := self ffiReturnPointer: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState]
  			ifFalse:
  				[oop := self ffiReturnStruct: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  		 ^oop].
  	
  	(atomicType >> 1) = (FFITypeSingleFloat >> 1)
  		ifTrue:
  			[oop := interpreterProxy floatObjectOf: floatRet]
  		ifFalse:
  			[oop := self ffiCreateIntegralResultOop: intRet
  						ofAtomicType: atomicType
  						in: calloutState].
  	^interpreterProxy methodReturnValue: oop!



More information about the Vm-dev mailing list