[Vm-dev] VM Maker: VMMaker.oscog-eem.1693.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Feb 23 02:45:18 UTC 2016


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1693.mcz

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

Name: VMMaker.oscog-eem.1693
Author: eem
Time: 22 February 2016, 6:43:36.966841 pm
UUID: 609488bc-c34d-49c6-8040-676e1a9d9d0e
Ancestors: VMMaker.oscog-eem.1692

Fix a bug in printHex: for 64-bits (faulty arithmetic).

Fix the remaining 64-bit issues in the ThreadedFFIPlugin.  The X64SysVFFIPlugin now passes the test suite.

The issues addressed are:
Masks for restricting and signing integral return values must be declared as at least long (again the fact that a manifest integer constat's type defaults to int causes problems).  Cast 1 << foo to 1 asUnsignedLong << foo in one place where it is required.

Use isFloatObject: rather than floatClass to test for floats since this works for both SmallFloat64 and BoxedFloat64 on 64-bit Spur.

Several pointer declarations needed to be e.g. <var: #ptr type: #'long *'>, not <var: #ptr type: #'int *'>.

Several casts to int of of firstIndexableField: (which has tyype void *) were discarded.

ExternalAddresses and the like need to be created with BytesPerWord or (self sizeof: #'void *'),, not 4.

Modify Slang to cast a manifest constant that is the receiver of a shift to long (via postpending 'L' to the numeric string).

Speed up ffiIntegerValueOf: by adding a tag test (harmless in our current crop of VMs) and cppIf: SPURVM as appropriate.

(N.B. not merging with VMMaker.oscog-EstebanLorenzano.1692.  The change there-in is incorrect.  Esteban and I have discussed and resolved the issue off line).

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

Item was changed:
  ----- Method: CCodeGenerator>>generateShiftLeft:on:indent: (in category 'C translation') -----
  generateShiftLeft: msgNode on: aStream indent: level
+ 	"Generate a C bitShift.  If we can determine the result would overflow the word size,
+ 	 cast to a long long integer. If the receiver is an integer constant make sure its type
+ 	 is long, since the default type of numeric constants is int, which plays havoc in 64-bits."
- 	"Generate a C bitShift.  If we can determine the result
- 	 would overflow the word size, cast to a long integer."
  	| rcvr arg valueBeyondInt castToLong |
  	rcvr := msgNode receiver.
  	arg := msgNode args first.
  	valueBeyondInt := 1 bitShift: 32. "The default type of const << N is int."
  	castToLong := vmClass notNil and: [vmClass objectMemoryClass wordSize = 8].
  	castToLong ifFalse:
  		[rcvr constantNumbericValueOrNil ifNotNil:
  			[:rcvrVal|
  			 arg constantNumbericValueOrNil ifNotNil:
  				[:argVal|
  				 castToLong := rcvrVal < valueBeyondInt
  								  and: [(rcvrVal bitShift: argVal) >= valueBeyondInt]]]].
  	castToLong
  		ifTrue:
  			[(rcvr isConstant and: [rcvr name isEmpty])
  				ifTrue:
  					[self emitCExpression: rcvr on: aStream.
  					 aStream nextPutAll: 'LL']
  				ifFalse:
  					[aStream nextPutAll: '((long)'.
  					 self emitCExpression: rcvr on: aStream.
  					 aStream nextPut: $)]]
  		ifFalse:
+ 			[self emitCExpression: rcvr on: aStream.
+ 			 (rcvr isConstant and: [rcvr name isEmpty]) ifTrue:
+ 				[aStream nextPut: $L]].
- 			[self emitCExpression: rcvr on: aStream].
  	aStream nextPutAll: ' << '.
  	self emitCExpression: arg on: aStream!

Item was changed:
  ----- Method: Interpreter>>printHex: (in category 'debug printing') -----
  printHex: n
  	"Print n in hex,  in the form '    0x1234', padded to a width of 10 characters
  	 in 32-bits ('0x' + 8 nibbles) or 18 characters in 64-bits ('0x' + 16 nibbles)"
  	<api>
  	| len buf |
+ 	<var: #buf declareC: 'char buf[37]'> "large enough for a 64-bit value in hex plus the null plus 16 spaces"
+ 	self cCode: 'memset(buf,'' '',36)' inSmalltalk: [buf := 'doh!!'].
- 	<var: #buf declareC: 'char buf[35]'> "large enough for a 64-bit value in hex plus the null plus 16 spaces"
- 	self cCode: 'memset(buf,'' '',34)' inSmalltalk: [buf := 'doh!!'].
  	len := self cCode: 'sprintf(buf + 2 + 2 * BytesPerWord, "0x%lx", (unsigned long)(n))'.
  	self cCode: 'printf("%s", buf + len)'.
  	len touch: buf!

Item was changed:
  ----- Method: StackInterpreter>>printHex: (in category 'debug printing') -----
  printHex: n
  	"Print n in hex,  in the form '    0x1234', padded to a width of 10 characters
  	 in 32-bits ('0x' + 8 nibbles) or 18 characters in 64-bits ('0x' + 16 nibbles)"
  	<api>
  	| len buf |
+ 	<var: #buf declareC: 'char buf[37]'> "large enough for a 64-bit value in hex plus the null plus 16 spaces"
+ 	self cCode: 'memset(buf,'' '',36)' inSmalltalk: [buf := 'doh!!'].
- 	<var: #buf declareC: 'char buf[35]'> "large enough for a 64-bit value in hex plus the null plus 16 spaces"
- 	self cCode: 'memset(buf,'' '',34)' inSmalltalk: [buf := 'doh!!'].
  	len := self cCode: 'sprintf(buf + 2 + 2 * BytesPerWord, "0x%lx", (unsigned long)(n))'.
  	self cCode: 'printf("%s", buf + len)'.
  	len touch: buf!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiCreateIntegralResultOop:ofAtomicType:in: (in category 'callout support') -----
  ffiCreateIntegralResultOop: retVal ofAtomicType: atomicType in: calloutState
  	<inline: true>
  	<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 << (byteSize * 8) - 1].
  		 ^value = 0
  			ifTrue:[interpreterProxy falseObject]
  			ifFalse:[interpreterProxy trueObject]].
  	atomicType <= FFITypeSignedInt ifTrue:
  		["these are all generall integer returns"
+ 		atomicType <= (BytesPerWord = 8 ifTrue: [FFITypeSignedInt] ifFalse: [FFITypeSignedShort]) ifTrue:
- 		atomicType <= FFITypeSignedShort ifTrue:
  			["byte/short. first extract partial word, then sign extend"
+ 			shift := (BytesPerWord = 8 and: [atomicType >= FFITypeUnsignedInt])
+ 						ifTrue: [32]
+ 						ifFalse: [(atomicType >> 1) * 8]. "# of significant bits"
+ 			value := retVal bitAnd: (1 asUnsignedLong << shift - 1). 
- 			shift := (atomicType >> 1) * 8. "# of significant bits"
- 			value := retVal bitAnd: (1 << shift - 1). 
  			(atomicType anyMask: 1) ifTrue:
  				["make the guy signed"
+ 				mask := 1 asUnsignedLong << (shift-1).
- 				mask := 1 << (shift-1).
  				value := (value bitAnd: mask-1) - (value bitAnd: mask)].
  			^interpreterProxy integerObjectOf: value].
+ 		"Word sized integer return"
- 		"32bit integer return"
  		^(atomicType anyMask: 1)
+ 			ifTrue:[interpreterProxy signedMachineIntegerFor: retVal] "signed return"
+ 			ifFalse:[interpreterProxy positiveMachineIntegerFor: retVal]]. "unsigned return"
- 			ifTrue:[interpreterProxy signed32BitIntegerFor: retVal] "signed return"
- 			ifFalse:[interpreterProxy positive32BitIntegerFor: retVal]]. "unsigned return"
  
  	"longlong, char"
  	^(atomicType >> 1) = (FFITypeSignedLongLong >> 1) 
  		ifTrue:
  			[(atomicType anyMask: 1)
  				ifTrue:[interpreterProxy signed64BitIntegerFor: retVal] "signed return"
  				ifFalse:[interpreterProxy positive64BitIntegerFor: retVal]]
  		ifFalse:
  			[interpreterProxy characterObjectOf: (retVal bitAnd: Byte0Mask)]!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiFloatValueOf: (in category 'callout support') -----
  ffiFloatValueOf: oop
  	"Support for generic callout. Return a float value that is coerced as C would do."
+ 	<returnTypeC: #double>
+ 	(interpreterProxy isFloatObject: oop) ifTrue:
+ 		[^interpreterProxy floatValueOf: oop].
- 	| oopClass |
- 	<returnTypeC:'double'>
- 	oopClass := interpreterProxy fetchClassOf: oop.
- 	oopClass = interpreterProxy classFloat
- 		ifTrue:[^interpreterProxy floatValueOf: oop].
  	"otherwise try the integer coercions and return its float value"
  	^(self ffiIntegerValueOf: oop) asFloat!

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."
- 	"Support for generic callout. Return an integer value that is coerced as C would do."
- 	| oopClass |
  	<inline: true>
+ 	"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 fetchClassOf: oop) = interpreterProxy classLargePositiveInteger ifTrue:
+ 				[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 isIntegerObject: oop) ifTrue:
- 		[^interpreterProxy integerValueOf: oop].
- 	oop = interpreterProxy nilObject ifTrue: [^0]. "@@: should we really allow this????"
- 	oop = interpreterProxy falseObject ifTrue: [^0].
- 	oop = interpreterProxy trueObject ifTrue: [^1].
- 	oopClass := interpreterProxy fetchClassOf: oop.
- 	oopClass = interpreterProxy classFloat ifTrue:
- 		[^(interpreterProxy floatValueOf: oop) asInteger].
- 	oopClass = interpreterProxy classCharacter ifTrue:
- 		[^interpreterProxy characterValueOf: oop].
- 	oopClass = interpreterProxy classLargePositiveInteger ifTrue:
- 		[^interpreterProxy positive32BitValueOf: oop].
  	^interpreterProxy signedMachineIntegerValueOf: oop "<- will fail if not integer"!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiLoadCalloutAddress: (in category 'symbol loading') -----
  ffiLoadCalloutAddress: lit
  	"Load the address of the foreign function from the given object"
  	| addressPtr address ptr |
+ 	<var: #ptr type: #'long *'>
- 	<var: #ptr type: #'int *'>
  	"Lookup the address"
  	addressPtr := interpreterProxy fetchPointer: 0 ofObject: lit.
  	"Make sure it's an external handle"
  	address := self ffiContentsOfHandle: addressPtr errCode: FFIErrorBadAddress.
  	interpreterProxy failed ifTrue:
  		[^0].
  	address = 0 ifTrue:"Go look it up in the module"
  		[self externalFunctionHasStackSizeSlot ifTrue:
  			[interpreterProxy
  				storePointer: ExternalFunctionStackSizeIndex
  				ofObject: lit
  				withValue: (interpreterProxy integerObjectOf: -1)].
  		(interpreterProxy slotSizeOf: lit) < 5 ifTrue:
  			[^self ffiFail: FFIErrorNoModule].
  		address := self ffiLoadCalloutAddressFrom: lit.
  		interpreterProxy failed ifTrue:
  			[^0].
  		"Store back the address"
  		ptr := interpreterProxy firstIndexableField: addressPtr.
  		ptr at: 0 put: address].
  	^address!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushPointerContentsOf:in: (in category 'marshalling') -----
  ffiPushPointerContentsOf: oop in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Push the contents of the given external structure"
  	| ptrClass ptrAddress |
  	<inline: false>
  	ptrClass := interpreterProxy fetchClassOf: oop.
+ 	ptrClass = interpreterProxy classExternalAddress ifTrue:
+ 		[ptrAddress := (interpreterProxy fetchPointer: 0 ofObject: oop) asVoidPointer.
- 	ptrClass = interpreterProxy classExternalAddress ifTrue:[
- 		ptrAddress := interpreterProxy fetchPointer: 0 ofObject: oop.
  		"Don't you dare to pass pointers into object memory"
  		(interpreterProxy isInMemory: ptrAddress) ifTrue:
  			[^FFIErrorInvalidPointer].
  		^self ffiPushPointer: ptrAddress in: calloutState].
  
  	ptrClass = interpreterProxy classByteArray ifTrue:
  		["Since this involves passing 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."
  		 self cppIf: COGMTVM ifTrue:
  		 [((calloutState callFlags anyMask: FFICallFlagThreaded)
  		   and: [interpreterProxy isYoung: oop]) ifTrue:
  			[^PrimErrObjectMayMove negated]].
  
+ 		ptrAddress := interpreterProxy firstIndexableField: oop.
- 		ptrAddress := self cCoerce: (interpreterProxy firstIndexableField: oop) to: #int.
  		^self ffiPushPointer: ptrAddress in: calloutState].
  
  	(interpreterProxy includesBehavior: ptrClass ThatOf: interpreterProxy classAlien) ifTrue:
  		[self cppIf: COGMTVM ifTrue:
  		 [((calloutState callFlags anyMask: FFICallFlagThreaded)
  		   and: [(self isDirectAlien: oop)
  		   and: [interpreterProxy isYoung: oop]]) ifTrue:
  			[^PrimErrObjectMayMove negated]].
  
  		ptrAddress := self startOfData: oop.
  		^self ffiPushPointer: ptrAddress in: calloutState].
  
  	^FFIErrorBadArg!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiPushStructureContentsOf:in: (in category 'callout support') -----
  ffiPushStructureContentsOf: oop in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	"Push the contents of the given external structure"
  	| ptrClass ptrAddress |
  	<inline: true>
  	ptrClass := interpreterProxy fetchClassOf: oop.
  	ptrClass = interpreterProxy classExternalAddress ifTrue: "ExternalAddress is bytes"
+ 		[ptrAddress := (interpreterProxy fetchPointer: 0 ofObject: oop) asVoidPointer.
- 		[ptrAddress :=interpreterProxy fetchPointer: 0 ofObject: oop.
  		"There is no way we can make sure the structure is valid.
  		But we can at least check for attempts to pass pointers to ST memory."
  		(interpreterProxy isInMemory: ptrAddress) ifTrue:
  			[^FFIErrorInvalidPointer].
+ 		^self ffiPushStructure: ptrAddress
- 		^self ffiPushStructure:  (self cCoerceSimple: ptrAddress to: #'void *')
  			ofSize: (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  			typeSpec: calloutState ffiArgSpec
  			ofLength: calloutState ffiArgSpecSize
  			in: calloutState].
  	ptrClass = interpreterProxy classByteArray ifTrue:
  		["The following is a somewhat pessimistic test but I like being sure..."
  		(interpreterProxy byteSizeOf: oop) = (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  			ifFalse:[^FFIErrorStructSize].
+ 		ptrAddress := interpreterProxy firstIndexableField: oop.
+ 		(calloutState ffiArgHeader anyMask: FFIFlagPointer) ifFalse:
- 		ptrAddress := self cCoerceSimple: (interpreterProxy firstIndexableField: oop) to: #int.
- 		(calloutState ffiArgHeader anyMask: FFIFlagPointer) ifFalse:[
  			"Since this involves passing 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."
+ 			[self cppIf: COGMTVM ifTrue:
- 			self cppIf: COGMTVM ifTrue:
  			 [((calloutState callFlags anyMask: FFICallFlagThreaded)
  			 and: [interpreterProxy isYoung: oop]) ifTrue:
  				[^PrimErrObjectMayMove negated]].
+ 			^self ffiPushStructure: ptrAddress
- 			^self ffiPushStructure: (self cCoerceSimple: ptrAddress to: #'void *') 
  				ofSize: (calloutState ffiArgHeader bitAnd: FFIStructSizeMask)
  				typeSpec: calloutState ffiArgSpec
  				ofLength: calloutState ffiArgSpecSize
  				in: calloutState].
  		"If FFIFlagPointer + FFIFlagStructure is set use ffiPushPointer on the contents"
  		(calloutState ffiArgHeader bitAnd: FFIStructSizeMask) = 4 ifFalse:
  			[^FFIErrorStructSize].
+ 		ptrAddress := (interpreterProxy fetchPointer: 0 ofObject: oop) asVoidPointer.
- 		ptrAddress := interpreterProxy fetchPointer: 0 ofObject: oop.
  		(interpreterProxy isInMemory: ptrAddress) ifTrue:
  			[^FFIErrorInvalidPointer].
  		^self ffiPushPointer: ptrAddress in: calloutState].
  	^FFIErrorBadArg!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>ffiReturnPointer:ofType:in: (in category 'callout support') -----
  ffiReturnPointer: retVal ofType: retType in: calloutState
  	<var: #calloutState type: #'CalloutState *'>
  	<var: #retVal type: #usqLong>
  	"Generic callout support. Create a pointer return value from an external function call"
  	| retClass atomicType retOop oop ptr classOop |
  	<var: #ptr type: #'sqInt *'>
  	retClass := interpreterProxy fetchPointer: 1 ofObject: retType.
  	retClass = interpreterProxy nilObject ifTrue:
  		["Create ExternalData upon return"
  		atomicType := self atomicTypeOf: calloutState ffiRetHeader.
  		(atomicType >> 1) = (FFITypeSignedChar >> 1) ifTrue: "String return"
  			[^self ffiReturnCStringFrom: (self cCoerceSimple: retVal to: #usqInt)].
  		"generate external data"
  		self remapOop: retType in:
  			[oop := interpreterProxy
  						instantiateClass: interpreterProxy classExternalAddress 
+ 						indexableSize: BytesPerWord.
- 						indexableSize: 4.
  			ptr := interpreterProxy firstIndexableField: oop.
  			ptr at: 0 put: (self cCoerceSimple: retVal to: #sqInt).
  			self remapOop: oop in:
  				[retOop := interpreterProxy 
  								instantiateClass: interpreterProxy classExternalData 
  								indexableSize: 0].
  			interpreterProxy storePointer: 0 ofObject: retOop withValue: oop].
  		interpreterProxy storePointer: 1 ofObject: retOop withValue: retType.
  		^interpreterProxy methodReturnValue: retOop].
  	"non-atomic pointer return"
  	classOop := (calloutState ffiRetHeader anyMask: FFIFlagStructure)
  					ifTrue:[interpreterProxy classByteArray]
  					ifFalse:[interpreterProxy classExternalAddress].
  	self remapOop: retClass in:
  		[oop := interpreterProxy 
  					instantiateClass: classOop
+ 					indexableSize: BytesPerWord].
- 					indexableSize: 4].
  	ptr := interpreterProxy firstIndexableField: oop.
  	ptr at: 0 put: (self cCoerceSimple: retVal to: #sqInt).
  	self remapOop: oop in:
  		[retOop := interpreterProxy instantiateClass: retClass indexableSize: 0].
  	interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
  	^interpreterProxy methodReturnValue: retOop!

Item was changed:
  ----- Method: ThreadedFFIPlugin>>primitiveLoadSymbolFromModule (in category 'primitives') -----
  primitiveLoadSymbolFromModule
  	"Attempt to find the address of a symbol in a loaded library.
  	loadSymbol: aSymbol fromModule: moduleName
  		<primitive: 'primitiveLoadSymbolFromModule' error: errorCode module: 'SqueakFFIPrims'>
  	"
  	<export: true>
  
  	| symbol module moduleHandle address oop ptr |
  
  	<var: #address type: #'void *'>
+ 	<var: #ptr type: #'void **'>
- 	<var: #ptr type:'unsigned int *'>
  	
  	interpreterProxy methodArgumentCount = 2 ifFalse:
  		[^interpreterProxy primitiveFailFor: PrimErrBadNumArgs].	
  
  	module := interpreterProxy stackValue: 0.
  	symbol := interpreterProxy stackValue: 1.
  
  	moduleHandle := self ffiLoadCalloutModule: module.
  	interpreterProxy failed ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNotFound].
  	address := interpreterProxy
+ 					ioLoadSymbol: (self cCoerce: (interpreterProxy firstIndexableField: symbol) to: #sqInt)
+ 					OfLength: (interpreterProxy byteSizeOf: symbol)
+ 					FromModule: moduleHandle.
- 		ioLoadSymbol: (self cCoerce: (interpreterProxy firstIndexableField: symbol) to: #sqInt)
- 		OfLength: (interpreterProxy byteSizeOf: symbol)
- 		FromModule: moduleHandle.
  	(interpreterProxy failed
  	 or: [address = 0]) ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNotFound].
  	
  	oop := interpreterProxy 
+ 			instantiateClass: interpreterProxy classExternalAddress 
+ 			indexableSize: (self sizeof: #'void *').
- 		instantiateClass: interpreterProxy classExternalAddress 
- 		indexableSize: 4.
  	ptr := interpreterProxy firstIndexableField: oop.
  	ptr at: 0 put: address.
  	
  	^interpreterProxy methodReturnValue: oop!

Item was changed:
  ----- Method: ThreadedX64FFIPlugin>>ffiPushSingleFloat:in: (in category 'marshalling') -----
  ffiPushSingleFloat: value in: calloutState
  	<var: #value type: #float>
  	<var: #calloutState type: #'CalloutState *'>
  	<inline: true>
  
  	calloutState floatRegisterIndex < NumFloatRegArgs
  		ifTrue:
+ 			[(self cCoerce: calloutState floatRegisters + calloutState floatRegisterIndex to: #'float *') at: 0 put: value.
- 			[calloutState floatRegisters at: calloutState floatRegisterIndex put: value.
  			 calloutState floatRegisterIndex: calloutState floatRegisterIndex + 1]
  		ifFalse:
  			[calloutState currentArg + WordSize > calloutState limit ifTrue:
  				[^FFIErrorCallFrameTooBig].
  			 interpreterProxy storeFloatAtPointer: calloutState currentArg from: value.
  			 calloutState currentArg: calloutState currentArg + WordSize].
  	^0!



More information about the Vm-dev mailing list