[Vm-dev] VM Maker Inbox: VMMaker.oscog-KenD.2513.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jan 23 16:31:48 UTC 2019


A new version of VMMaker was added to project VM Maker Inbox:
http://source.squeak.org/VMMakerInbox/VMMaker.oscog-KenD.2513.mcz

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

Name: VMMaker.oscog-KenD.2513
Author: KenD
Time: 23 January 2019, 8:30:03.772198 am
UUID: 5ca2e0fe-bdad-4047-a9d8-8fc9f9c9cd3c
Ancestors: VMMaker.oscog-KenD.2512

Reversed the way single and double floats were handled in callOutState floatRegisters to simplify the  logic a bit.

=============== Diff against VMMaker.oscog-KenD.2512 ===============

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

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>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 |
  	<var: #floatRet type: #double>
  	<var: #intRet type: #usqLong>
  	<inline: true>
  	myThreadIndex := interpreterProxy disownVM: (self disownFlagsFor: calloutState).
  
  	calloutState floatRegisterIndex > 0 ifTrue:
  		[self loadFloatRegs:
+ 			   (calloutState floatRegisters at: 0)
+ 			_: (calloutState floatRegisters at: 1)
+ 			_: (calloutState floatRegisters at: 2)
+ 			_: (calloutState floatRegisters at: 3)
+ 			_: (calloutState floatRegisters at: 4)
+ 			_: (calloutState floatRegisters at: 5)
+ 			_: (calloutState floatRegisters at: 6)
+ 			_: (calloutState floatRegisters at: 7)].
- 			   ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 0)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 2)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 4)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 6)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 8)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 10)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 12)) to: #'double *') at: 0)
- 			_: ((self cCoerceSimple: (self addressOf: (calloutState floatRegisters at: 14)) to: #'double *') at: 0)].
  
  	(self allocaLiesSoSetSpBeforeCall or: [self mustAlignStack]) ifTrue:
  		[self setsp: calloutState argVector].
  
  	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, sqIntptr_t, sqIntptr_t)')
  					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)
  					with: (calloutState integerRegisters at: 6)
  					with: (calloutState integerRegisters at: 7)]
  			ifFalse: "atomicType = FFITypeDoubleFloat"
  				[floatRet := self 
  					dispatchFunctionPointer: (self cCoerceSimple: procAddr to: 'double (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')
  					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)
  					with: (calloutState integerRegisters at: 6)
  					with: (calloutState integerRegisters at: 7)].
  
  		 "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: 'usqIntptr_t (*)(sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t, sqIntptr_t)')
  				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)
  				with: (calloutState integerRegisters at: 6)
  				with: (calloutState integerRegisters at: 7).
  
  	"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: intRet ofType: (self ffiReturnType: specOnStack) in: calloutState].
  	
  	^self ffiCreateIntegralResultOop: intRet ofAtomicType: atomicType in: calloutState!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushDoubleFloat:in: (in category 'marshalling') -----
  ffiPushDoubleFloat: value in: calloutState
  	<var: #value type: #double>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: #always>
  
+ 	calloutState floatRegisterIndex < NumFloatRegArgs
- 	calloutState floatRegisterIndex < (NumFloatRegArgs - 1)
  		ifTrue:
+ 			[calloutState floatRegisters
+ 				at: calloutState floatRegisterIndex
- 			[(self cCoerceSimple: 
- 				(self addressOf: (calloutState floatRegisters at: calloutState floatRegisterIndex)) 
- 					 to: 'double*')
- 				at: 0
  				put: value.
+ 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 1]
- 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 2]
  		ifFalse:
  			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 calloutState floatRegisterIndex: NumFloatRegArgs.
  			 interpreterProxy storeFloatAtPointer: calloutState currentArg from: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
  	^0!

Item was changed:
  ----- Method: ThreadedARM64FFIPlugin>>ffiPushSingleFloat:in: (in category 'marshalling') -----
  ffiPushSingleFloat: value in: calloutState
  	<var: #value type: #float>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: #always>
  	calloutState floatRegisterIndex < NumFloatRegArgs
+ 		ifTrue: "Note: this is a 'memcopy', so size is preserved. Casting to #double changes the size"
+ 			[(self cCoerceSimple: 
+ 				(self addressOf: (calloutState floatRegisters at: calloutState floatRegisterIndex)) 
+ 					 to: 'float*')
+ 				at: 0
+ 				put: value.
+ 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 1]
- 		ifTrue: 
- 			[calloutState floatRegisters 
- 				at: calloutState floatRegisterIndex 
- 				put: (self cCoerceSimple: value to: #double).
- 			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 2]
  		ifFalse:
  			[calloutState currentArg + self wordSize > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 interpreterProxy storeSingleFloatAtPointer: calloutState currentArg from: value.
  			 calloutState currentArg: calloutState currentArg + self wordSize].
  	^0!

Item was changed:
  ----- Method: ThreadedFFICalloutStateForARM64 class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a ThreadedFFICalloutState struct."
  
  	superclass instVarNamesAndTypesForTranslationDo: aBinaryBlock.
  	self instVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
+ 						['integerRegisters']	-> [{#sqInt.   '[NumIntRegArgs]'   }].
+ 						['floatRegisters']	-> [{#double. '[NumFloatRegArgs]'}] }
- 						['integerRegisters']	-> [{#sqInt. '[NumIntRegArgs]'}].
- 						['floatRegisters']	-> [{#float. '[NumFloatRegArgs]'}] }
  					otherwise:
  						[#sqInt])]!



More information about the Vm-dev mailing list