[commit] r2234 - OSCogVM source as per VMMaker-oscog.21. Fix struct return, indexing return type

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

[commit] r2234 - OSCogVM source as per VMMaker-oscog.21. Fix struct return, indexing return type

commits-3
 
Author: eliot
Date: 2010-07-13 18:10:33 -0700 (Tue, 13 Jul 2010)
New Revision: 2234

Removed:
   branches/Cog/platforms/win32/plugins/SqueakFFIPrims/
Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/macbuild/SqueakFFIPrims/SqueakFFI.xcodeproj/project.pbxproj
   branches/Cog/platforms/Cross/plugins/SqueakFFIPrims/sqFFITestFuncs.c
   branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile
   branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile.in
   branches/Cog/src/plugins/Matrix2x3Plugin/Matrix2x3Plugin.c
   branches/Cog/src/plugins/SqueakFFIPrims/SqueakFFIPrims.c
Log:
OSCogVM source as per VMMaker-oscog.21.  Fix struct return, indexing return type
spec corrrectly and not being confused between the struct return size and
whether return is via registers or not.  Include the FFI test funcs in the
plugin. Backwards-compatibility access to ffi error code.


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-14 01:10:33 UTC (rev 2234)
@@ -120192,4 +120192,486 @@
  platformDir: (FileDirectory default / '../platforms') fullName
  excluding: (InterpreterPlugin withAllSubclasses collect: [:ea| ea name])!
 
-----QUIT----{11 July 2010 . 9:11:50 am} VMMaker-Squeak4.1.image priorSource: 4882544!
\ No newline at end of file
+----QUIT----{11 July 2010 . 9:11:50 am} VMMaker-Squeak4.1.image priorSource: 4882544!
+
+----STARTUP----{13 July 2010 . 10:02:40 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{13 July 2010 . 10:03:01 am} VMMaker-Squeak4.1.image priorSource: 4893204!
+
+----STARTUP----{13 July 2010 . 10:03:58 am} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{13 July 2010 . 11:06:14 am} VMMaker-Squeak4.1.image priorSource: 4893204!
+
+----STARTUP----{13 July 2010 . 5:34:17 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+!ReentrantFFIPlugin methodsFor: 'callout support' stamp: 'eem 7/13/2010 16:04' prior: 38422979!
+ffiCall: externalFunction ArgArrayOrNil: argArrayOrNil NumArgs: nArgs
+ "Generic callout. Does the actual work.  If argArrayOrNil is nil it takes args from the stack
+ and the spec from the method.  If argArrayOrNil is not nil takes args from argArrayOrNil
+ and the spec from the receiver."
+ | flags argTypeArray address argType oop argSpec argClass err theCalloutState calloutState requiredStackSize stackSize allocation result |
+ <inline: true>
+ <var: #theCalloutState type: #'CalloutState'>
+ <var: #calloutState type: #'CalloutState *'>
+ <var: #allocation type: #'char *'>
+
+ (interpreterProxy is: externalFunction KindOfClass: interpreterProxy classExternalFunction) ifFalse:
+ [^self ffiFail: FFIErrorNotFunction].
+ "Load and check the values in the externalFunction before we call out"
+ flags := interpreterProxy fetchInteger: ExternalFunctionFlagsIndex ofObject: externalFunction.
+ interpreterProxy failed ifTrue:
+ [^self ffiFail: FFIErrorBadArgs].
+ argTypeArray := interpreterProxy fetchPointer: ExternalFunctionArgTypesIndex ofObject: externalFunction.
+ "must be array of arg types"
+ ((interpreterProxy isArray: argTypeArray)
+ and: [(interpreterProxy slotSizeOf: argTypeArray) = (nArgs + 1)]) ifFalse:
+ [^self ffiFail: FFIErrorBadArgs].
+ "check if the calling convention is supported"
+ (self ffiSupportsCallingConvention: flags) ifFalse:
+ [^self ffiFail: FFIErrorCallType].
+
+ address := self ffiLoadCalloutAddress: externalFunction.
+ interpreterProxy failed ifTrue:
+ [^0 "error code already set by ffiLoadCalloutAddress:"].
+ requiredStackSize := self externalFunctionHasStackSizeSlot
+ ifTrue: [interpreterProxy fetchInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction]
+ ifFalse: [-1].
+ interpreterProxy failed ifTrue:
+ [^interpreterProxy primitiveFailFor: (argArrayOrNil isNil
+ ifTrue: [PrimErrBadMethod]
+ ifFalse: [PrimErrBadReceiver])].
+ stackSize := requiredStackSize < 0 ifTrue: [DefaultMaxStackSize] ifFalse: [requiredStackSize].
+ self cCode: [] inSmalltalk: [theCalloutState := self class calloutStateClass new].
+ calloutState := self addressOf: theCalloutState.
+ self cCode: [self me: calloutState ms: 0 et: (self sizeof: #CalloutState asSymbol)].
+ calloutState callFlags: flags.
+ "Fetch return type and args"
+ argType := interpreterProxy fetchPointer: 0 ofObject: argTypeArray.
+ argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
+ argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
+ (err := self ffiCheckReturn: argSpec With: argClass in: calloutState) ~= 0 ifTrue:
+ [^self ffiFail: err]. "cannot return"
+ "alloca the outgoing stack frame, leaving room for register args while marshalling, and including space for the return struct, if any."
+ allocation := self alloca: stackSize + calloutState structReturnSize + self registerArgsSlop + self cStackAlignment.
+ self allocaLiesSoUseGetsp ifTrue:
+ [allocation := self getsp].
+ self cStackAlignment ~= 0 ifTrue:
+ [allocation := self cCoerce: (allocation asUnsignedInteger bitAnd: (self cStackAlignment - 1) bitInvert32)
+ to: #'char *'].
+ calloutState
+ argVector: allocation;
+ currentArg: allocation + self registerArgsSlop;
+ limit: allocation + stackSize + self registerArgsSlop.
+ (calloutState structReturnSize > 0
+ and: [self nonRegisterStructReturnIsViaImplicitFirstArgument
+ and: [(self returnStructInRegisters: calloutState structReturnSize) not]]) ifTrue:
+ [self ffiPushPointer: calloutState limit in: calloutState].
+ 1 to: nArgs do:
+ [:i|
+ argType := interpreterProxy fetchPointer: i ofObject: argTypeArray.
+ argSpec := interpreterProxy fetchPointer: 0 ofObject: argType.
+ argClass := interpreterProxy fetchPointer: 1 ofObject: argType.
+ oop := argArrayOrNil isNil
+ ifTrue: [interpreterProxy stackValue: nArgs - i]
+ ifFalse: [interpreterProxy fetchPointer: i - 1 ofObject: argArrayOrNil].
+ err := self ffiArgument: oop Spec: argSpec Class: argClass in: calloutState.
+ err ~= 0 ifTrue:
+ [self cleanupCalloutState: calloutState.
+ ^self ffiFail: err]]. "coercion failed or out of stack space"
+ "Failures must be reported back from ffiArgument:Spec:Class:in:.
+ Should not fail form here on in."
+ self assert: interpreterProxy failed not.
+ self ffiLogCallout: externalFunction.
+ (requiredStackSize < 0
+ and: [self externalFunctionHasStackSizeSlot]) ifTrue:
+ [stackSize := calloutState currentArg - calloutState argVector.
+ interpreterProxy storeInteger: ExternalFunctionStackSizeIndex ofObject: externalFunction withValue: stackSize].
+ "Go out and call this guy"
+ result := self ffiCalloutTo: address SpecOnStack: argArrayOrNil notNil in: calloutState.
+ self cleanupCalloutState: calloutState.
+ ^result! !
+!ReentrantFFIPlugin methodsFor: 'callout support' stamp: 'eem 7/13/2010 15:43' prior: 38358920!
+ffiCheckReturn: retSpec With: retClass in: calloutState
+ <var: #calloutState type: #'CalloutState *'>
+ "Make sure we can return an object of the given type"
+ <inline: true>
+ | ffiRetSpec |
+ retClass == interpreterProxy nilObject ifFalse:[
+ (interpreterProxy includesBehavior: retClass
+ ThatOf: interpreterProxy classExternalStructure)
+ ifFalse:[^FFIErrorBadReturn]].
+
+ (interpreterProxy isWords: retSpec)
+ ifFalse:[^FFIErrorWrongType].
+ (interpreterProxy slotSizeOf: retSpec) = 0 ifTrue:[^FFIErrorWrongType].
+ ffiRetSpec := self cCoerce: (interpreterProxy firstIndexableField: retSpec) to: #int.
+ calloutState ffiRetHeader: (interpreterProxy longAt: ffiRetSpec).
+ (self isAtomicType: calloutState ffiRetHeader) ifFalse:[
+ (retClass == interpreterProxy nilObject)
+ ifTrue:[^FFIErrorBadReturn]].
+ (calloutState ffiRetHeader bitAnd: (FFIFlagPointer bitOr: FFIFlagStructure)) = FFIFlagStructure ifTrue:
+ [calloutState structReturnSize: (calloutState ffiRetHeader bitAnd: FFIStructSizeMask)].
+ ^0! !
+!ReentrantFFIPlugin methodsFor: 'callout support' stamp: 'eem 7/13/2010 14:32' prior: 38362426!
+ffiFail: reason
+ <inline: false>
+ "Map the FFI error code into a primitive error code.  If reason is negative it encodes one of the
+ standard PrimErr... codes, negated to distinguish it from the FFIError codes.  If it is an FFIError...
+ code then add the size of the primitive error table + 2 to disambiguate it from the PrimErr... codes.
+ For historic reasons the FFIError codes range from -1 on up hence adding size + 2 maps them to
+ size of table + 1 on up.  This OFFSET IS undone by ExternalFunction class>>externalCallFailedWith:.
+ Thus we can communicate back both PrimErr.. and FFIError codes.  Complex but necessary."
+ ffiLastError := reason.
+ ^interpreterProxy primitiveFailFor:
+ (reason >= FFINoCalloutAvailable
+ ifTrue: [reason + 2 + (interpreterProxy slotSizeOf: interpreterProxy primitiveErrorTable)]
+ ifFalse: [reason negated])! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:27' prior: 38382066!
+primitiveFFIAllocate
+ "Primitive. Allocate an object on the external heap."
+ | byteSize addr oop ptr |
+ <export: true>
+ <inline: false>
+ <var: #ptr type:'int *'>
+ byteSize := interpreterProxy stackIntegerValue: 0.
+ interpreterProxy failed ifTrue:[^nil].
+ addr := self ffiAlloc: byteSize.
+ addr = 0 ifTrue:[^interpreterProxy primitiveFail].
+ oop := interpreterProxy
+ instantiateClass: interpreterProxy classExternalAddress
+ indexableSize: 4.
+ ptr := interpreterProxy firstIndexableField: oop.
+ ptr at: 0 put: addr.
+ interpreterProxy pop: 2 thenPush: oop! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:27' prior: 38383471!
+primitiveFFIDoubleAtPut
+ "Return a (signed or unsigned) n byte integer from the given byte offset."
+ | byteOffset rcvr addr floatValue floatOop |
+ <export: true>
+ <inline: false>
+ <var: #floatValue type:'double '>
+ floatOop := interpreterProxy stackValue: 0.
+ (interpreterProxy isIntegerObject: floatOop)
+ ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:'double']
+ ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:'double'].
+ byteOffset := interpreterProxy stackIntegerValue: 1.
+ rcvr := interpreterProxy stackObjectValue: 2.
+ interpreterProxy failed ifTrue:[^0].
+ addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.
+ interpreterProxy failed ifTrue:[^0].
+ self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
+ self cCode:'((int*)addr)[1] = ((int*)(&floatValue))[1]'.
+ interpreterProxy pop: 3 thenPush: floatOop! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:27' prior: 38385151!
+primitiveFFIFloatAtPut
+ "Return a (signed or unsigned) n byte integer from the given byte offset."
+ | byteOffset rcvr addr floatValue floatOop |
+ <export: true>
+ <inline: false>
+ <var: #floatValue type:'float '>
+ floatOop := interpreterProxy stackValue: 0.
+ (interpreterProxy isIntegerObject: floatOop)
+ ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:'float']
+ ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:'float'].
+ byteOffset := interpreterProxy stackIntegerValue: 1.
+ rcvr := interpreterProxy stackObjectValue: 2.
+ interpreterProxy failed ifTrue:[^0].
+ addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.
+ interpreterProxy failed ifTrue:[^0].
+ self cCode:'((int*)addr)[0] = ((int*)(&floatValue))[0]'.
+ interpreterProxy pop: 3 thenPush: floatOop! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/13/2010 14:36' prior: 38386896!
+primitiveFFIGetLastError
+ "Primitive. Return the error code from a failed call to the foreign function interface.
+ This is for backwards-compatibility.  Thread-safe access to the error code is via the
+ primitive error code."
+ <export: true>
+ <inline: false>
+ interpreterProxy pop: 1.
+ ^interpreterProxy pushInteger: ffiLastError! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:28' prior: 38387286!
+primitiveFFIIntegerAt
+ "Return a (signed or unsigned) n byte integer from the given byte offset."
+ | isSigned byteSize byteOffset rcvr addr value mask |
+ <export: true>
+ <inline: false>
+ isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).
+ byteSize := interpreterProxy stackIntegerValue: 1.
+ byteOffset := interpreterProxy stackIntegerValue: 2.
+ rcvr := interpreterProxy stackObjectValue: 3.
+ interpreterProxy failed ifTrue:[^0].
+ (byteOffset > 0 and:[byteSize = 1 or:[byteSize = 2 or:[byteSize = 4]]])
+ ifFalse:[^interpreterProxy primitiveFail].
+ addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.
+ interpreterProxy failed ifTrue:[^0].
+ byteSize < 4 ifTrue:[
+ "short/byte"
+ byteSize = 1
+ ifTrue:[value := interpreterProxy byteAt: addr]
+ ifFalse:[ value := self cCode: '*((short int *) addr)'
+ inSmalltalk: [interpreterProxy shortAt: addr]].
+ isSigned ifTrue:["sign extend value"
+ mask := 1 << (byteSize * 8 - 1).
+ value := (value bitAnd: mask-1) - (value bitAnd: mask)].
+ "note: byte/short never exceed SmallInteger range"
+ value := interpreterProxy integerObjectOf: value.
+ ] ifFalse:[
+ "general 32 bit integer"
+ value := interpreterProxy longAt: addr.
+ value := isSigned
+ ifTrue:[interpreterProxy signed32BitIntegerFor: value]
+ ifFalse:[interpreterProxy positive32BitIntegerFor: value].
+ ].
+ interpreterProxy pop: 4 thenPush: value! !
+!ReentrantFFIPlugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:28' prior: 38388824!
+primitiveFFIIntegerAtPut
+ "Store a (signed or unsigned) n byte integer at the given byte offset."
+ | isSigned byteSize byteOffset rcvr addr value max valueOop |
+ <export: true>
+ <inline: false>
+ isSigned := interpreterProxy booleanValueOf: (interpreterProxy stackValue: 0).
+ byteSize := interpreterProxy stackIntegerValue: 1.
+ valueOop := interpreterProxy stackValue: 2.
+ byteOffset := interpreterProxy stackIntegerValue: 3.
+ rcvr := interpreterProxy stackObjectValue: 4.
+ interpreterProxy failed ifTrue:[^0].
+ (byteOffset > 0 and:[byteSize = 1 or:[byteSize = 2 or:[byteSize = 4]]])
+ ifFalse:[^interpreterProxy primitiveFail].
+ addr := self ffiAddressOf: rcvr startingAt: byteOffset size: byteSize.
+ interpreterProxy failed ifTrue:[^0].
+ isSigned
+ ifTrue:[value := interpreterProxy signed32BitValueOf: valueOop]
+ ifFalse:[value := interpreterProxy positive32BitValueOf: valueOop].
+ interpreterProxy failed ifTrue:[^0].
+ byteSize < 4 ifTrue:[
+ isSigned ifTrue:[
+ max := 1 << (8 * byteSize - 1).
+ value >= max ifTrue:[^interpreterProxy primitiveFail].
+ value < (0 - max) ifTrue:[^interpreterProxy primitiveFail].
+ ] ifFalse:[
+ value >= (1 << (8*byteSize)) ifTrue:[^interpreterProxy primitiveFail].
+ ].
+ "short/byte"
+ byteSize = 1
+ ifTrue:[interpreterProxy byteAt: addr put: value]
+ ifFalse:[ self cCode: '*((short int *) addr) = value'
+ inSmalltalk: [interpreterProxy shortAt: addr put: value]].
+ ] ifFalse:[interpreterProxy longAt: addr put: value].
+ interpreterProxy pop: 5 thenPush: valueOop! !
+!ReentrantIA32FFIPlugin methodsFor: 'callout support' stamp: 'eem 7/13/2010 15:15' prior: 38405543!
+ffiReturnStruct: longLongRet ofType: ffiRetType in: calloutState
+ <var: #longLongRet type: #usqLong>
+ <var: #calloutState type: #'CalloutState *'>
+ "Create a structure return value from an external function call.  The value as been stored in
+ alloca'ed space pointed to by the calloutState."
+ | retOop retClass oop |
+ <inline: true>
+ retClass := interpreterProxy fetchPointer: 1 ofObject: ffiRetType.
+ retOop := interpreterProxy instantiateClass: retClass indexableSize: 0.
+ interpreterProxy pushRemappableOop: retOop.
+ oop := interpreterProxy
+ instantiateClass: interpreterProxy classByteArray
+ indexableSize: calloutState structReturnSize.
+ (self returnStructInRegisters: calloutState structReturnSize)
+ ifTrue:
+ [self mem: (interpreterProxy firstIndexableField: oop) cp: (self addressOf: longLongRet) y: calloutState structReturnSize]
+ ifFalse:
+ [self mem: (interpreterProxy firstIndexableField: oop) cp: calloutState limit y: calloutState structReturnSize].
+ retOop := interpreterProxy popRemappableOop.
+ interpreterProxy storePointer: 0 ofObject: retOop withValue: oop.
+ ^interpreterProxy methodReturnValue: retOop! !
+!Matrix2x3Plugin methodsFor: 'private' stamp: 'eem 7/10/2010 21:38' prior: 36384095!
+roundAndStoreResultPoint: nItemsToPop
+ "Store the result of a previous operation.
+ Fail if we cannot represent the result as SmallInteger"
+ m23ResultX := m23ResultX + 0.5.
+ m23ResultY := m23ResultY + 0.5.
+ (self okayIntValue: m23ResultX) ifFalse:[^interpreterProxy primitiveFail].
+ (self okayIntValue: m23ResultY) ifFalse:[^interpreterProxy primitiveFail].
+ interpreterProxy pop: nItemsToPop thenPush:
+ (interpreterProxy makePointwithxValue: m23ResultX asInteger
+ yValue: m23ResultY asInteger)! !
+!Matrix2x3Plugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:37' prior: 38210188!
+primitiveComposeMatrix
+ <export: true>
+ | m1 m2 m3 result |
+ <inline: false>
+ <var: #m1 type: #'float *'>
+ <var: #m2 type: #'float *'>
+ <var: #m3 type: #'float *'>
+ self cCode: ''  "Make this fail in simulation"
+ inSmalltalk: [interpreterProxy success: false. ^ nil].
+ m3 := self loadArgumentMatrix: (result := interpreterProxy stackObjectValue: 0).
+ m2 := self loadArgumentMatrix: (interpreterProxy stackObjectValue: 1).
+ m1 := self loadArgumentMatrix: (interpreterProxy stackObjectValue: 2).
+ interpreterProxy failed ifTrue:[^nil].
+ self matrix2x3ComposeMatrix: m1 with: m2 into: m3.
+ interpreterProxy pop: 3 thenPush: result! !
+!Matrix2x3Plugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:37' prior: 36389583!
+primitiveInvertRectInto
+ | matrix srcOop dstOop originX originY cornerX cornerY minX maxX minY maxY |
+ <export: true>
+ <inline: false>
+ <var: #matrix type:'float *'>
+ <var: #originX type:'double '>
+ <var: #originY type:'double '>
+ <var: #cornerX type:'double '>
+ <var: #cornerY type:'double '>
+ <var: #minX type:'double '>
+ <var: #maxX type:'double '>
+ <var: #minY type:'double '>
+ <var: #maxY type:'double '>
+
+ dstOop := interpreterProxy stackObjectValue: 0.
+ srcOop := interpreterProxy stackObjectValue: 1.
+ matrix := self loadArgumentMatrix: (interpreterProxy stackObjectValue: 2).
+ interpreterProxy failed ifTrue:[^nil].
+
+ (interpreterProxy fetchClassOf: srcOop) = (interpreterProxy fetchClassOf: dstOop)
+ ifFalse:[^interpreterProxy primitiveFail].
+ (interpreterProxy isPointers: srcOop)
+ ifFalse:[^interpreterProxy primitiveFail].
+ (interpreterProxy slotSizeOf: srcOop) = 2
+ ifFalse:[^interpreterProxy primitiveFail].
+
+ "Load top-left point"
+ self loadArgumentPoint: (interpreterProxy fetchPointer: 0 ofObject: srcOop).
+ interpreterProxy failed ifTrue:[^nil].
+ originX := m23ArgX.
+ originY := m23ArgY.
+ self matrix2x3InvertPoint: matrix.
+ minX := maxX := m23ResultX.
+ minY := maxY := m23ResultY.
+
+ "Load bottom-right point"
+ self loadArgumentPoint:(interpreterProxy fetchPointer: 1 ofObject: srcOop).
+ interpreterProxy failed ifTrue:[^nil].
+ cornerX := m23ArgX.
+ cornerY := m23ArgY.
+ self matrix2x3InvertPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ "Load top-right point"
+ m23ArgX := cornerX.
+ m23ArgY := originY.
+ self matrix2x3InvertPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ "Load bottom-left point"
+ m23ArgX := originX.
+ m23ArgY := cornerY.
+ self matrix2x3InvertPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ interpreterProxy failed ifFalse:[
+ dstOop := self roundAndStoreResultRect: dstOop x0: minX y0: minY x1: maxX y1: maxY].
+ interpreterProxy failed ifFalse:[
+ interpreterProxy pop: 3 thenPush: dstOop
+ ]! !
+!Matrix2x3Plugin methodsFor: 'primitives' stamp: 'eem 7/10/2010 21:37' prior: 36393650!
+primitiveTransformRectInto
+ | matrix srcOop dstOop originX originY cornerX cornerY minX maxX minY maxY |
+ <export: true>
+ <inline: false>
+ <var: #matrix type:'float *'>
+ <var: #originX type:'double '>
+ <var: #originY type:'double '>
+ <var: #cornerX type:'double '>
+ <var: #cornerY type:'double '>
+ <var: #minX type:'double '>
+ <var: #maxX type:'double '>
+ <var: #minY type:'double '>
+ <var: #maxY type:'double '>
+
+ dstOop := interpreterProxy stackObjectValue: 0.
+ srcOop := interpreterProxy stackObjectValue: 1.
+ matrix := self loadArgumentMatrix: (interpreterProxy stackObjectValue: 2).
+ interpreterProxy failed ifTrue:[^nil].
+
+ (interpreterProxy fetchClassOf: srcOop) = (interpreterProxy fetchClassOf: dstOop)
+ ifFalse:[^interpreterProxy primitiveFail].
+ (interpreterProxy isPointers: srcOop)
+ ifFalse:[^interpreterProxy primitiveFail].
+ (interpreterProxy slotSizeOf: srcOop) = 2
+ ifFalse:[^interpreterProxy primitiveFail].
+
+ "Load top-left point"
+ self loadArgumentPoint: (interpreterProxy fetchPointer: 0 ofObject: srcOop).
+ interpreterProxy failed ifTrue:[^nil].
+ originX := m23ArgX.
+ originY := m23ArgY.
+ self matrix2x3TransformPoint: matrix.
+ minX := maxX := m23ResultX.
+ minY := maxY := m23ResultY.
+
+ "Load bottom-right point"
+ self loadArgumentPoint:(interpreterProxy fetchPointer: 1 ofObject: srcOop).
+ interpreterProxy failed ifTrue:[^nil].
+ cornerX := m23ArgX.
+ cornerY := m23ArgY.
+ self matrix2x3TransformPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ "Load top-right point"
+ m23ArgX := cornerX.
+ m23ArgY := originY.
+ self matrix2x3TransformPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ "Load bottom-left point"
+ m23ArgX := originX.
+ m23ArgY := cornerY.
+ self matrix2x3TransformPoint: matrix.
+ minX := minX min: m23ResultX.
+ maxX := maxX max: m23ResultX.
+ minY := minY min: m23ResultY.
+ maxY := maxY max: m23ResultY.
+
+ dstOop := self roundAndStoreResultRect: dstOop x0: minX y0: minY x1: maxX y1: maxY.
+ interpreterProxy failed ifFalse:[
+ interpreterProxy pop: 3 thenPush: dstOop
+ ]! !
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+"VMMaker"!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+VMMaker
+ generate: CoInterpreter
+ to: (FileDirectory default / '../src') fullName
+ platformDir: (FileDirectory default / '../platforms') fullName
+ excluding:#(BrokenPlugin IA32ABIPluginSimulator SlangTestPlugin TestOSAPlugin
+ FFIPlugin ReentrantARMFFIPlugin ReentrantFFIPlugin ReentrantPPCBEFFIPlugin)!
+
+----QUIT----{13 July 2010 . 5:53:45 pm} VMMaker-Squeak4.1.image priorSource: 4893204!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)

Modified: branches/Cog/macbuild/SqueakFFIPrims/SqueakFFI.xcodeproj/project.pbxproj
===================================================================
--- branches/Cog/macbuild/SqueakFFIPrims/SqueakFFI.xcodeproj/project.pbxproj 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/macbuild/SqueakFFIPrims/SqueakFFI.xcodeproj/project.pbxproj 2010-07-14 01:10:33 UTC (rev 2234)
@@ -11,6 +11,7 @@
  730BD72610AA25350023C110 /* SqueakFFIPrims.c in Sources */ = {isa = PBXBuildFile; fileRef = 730BD72510AA25350023C110 /* SqueakFFIPrims.c */; };
  730BD72810AA26D00023C110 /* sqFFIPlugin.c in Sources */ = {isa = PBXBuildFile; fileRef = 730BD72710AA26D00023C110 /* sqFFIPlugin.c */; };
  730BD73110AA277B0023C110 /* SqueakPlugin.icns in Resources */ = {isa = PBXBuildFile; fileRef = 730BD73010AA277B0023C110 /* SqueakPlugin.icns */; };
+ 7386749111ED15E500E5B738 /* sqFFITestFuncs.c in Sources */ = {isa = PBXBuildFile; fileRef = 7386749011ED15E500E5B738 /* sqFFITestFuncs.c */; };
  8D576314048677EA00EA77CD /* CoreFoundation.framework in Frameworks */ = {isa = PBXBuildFile; fileRef = 0AA1909FFE8422F4C02AAC07 /* CoreFoundation.framework */; };
 /* End PBXBuildFile section */
 
@@ -25,6 +26,7 @@
  730BD72F10AA27590023C110 /* sqVirtualMachine.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; name = sqVirtualMachine.h; path = ../../platforms/Cross/vm/sqVirtualMachine.h; sourceTree = SOURCE_ROOT; };
  730BD73010AA277B0023C110 /* SqueakPlugin.icns */ = {isa = PBXFileReference; lastKnownFileType = image.icns; name = SqueakPlugin.icns; path = ../resources/ProjectBuilder/SqueakPlugin.icns; sourceTree = SOURCE_ROOT; };
  733EFEAC10B4D31C00A2FDA5 /* sqFFI.h */ = {isa = PBXFileReference; explicitFileType = sourcecode.c.h; fileEncoding = 4; name = sqFFI.h; path = ../../platforms/Cross/plugins/SqueakFFIPrims/sqFFI.h; sourceTree = SOURCE_ROOT; };
+ 7386749011ED15E500E5B738 /* sqFFITestFuncs.c */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.c; name = sqFFITestFuncs.c; path = ../../platforms/Cross/plugins/SqueakFFIPrims/sqFFITestFuncs.c; sourceTree = SOURCE_ROOT; };
  739A636B10AA442600F87ADB /* sqConfig.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; name = sqConfig.h; path = "../../platforms/Mac OS/vm/sqConfig.h"; sourceTree = SOURCE_ROOT; };
  739A636C10AA444800F87ADB /* sqPlatformSpecific.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; name = sqPlatformSpecific.h; path = "../../platforms/Mac OS/vm/sqPlatformSpecific.h"; sourceTree = SOURCE_ROOT; };
  739BEEE011C96C240093BD8A /* sq.h */ = {isa = PBXFileReference; fileEncoding = 4; lastKnownFileType = sourcecode.c.h; name = sq.h; path = ../../platforms/Cross/vm/sq.h; sourceTree = SOURCE_ROOT; };
@@ -76,6 +78,7 @@
  08FB77AFFE84173DC02AAC07 /* Source */ = {
  isa = PBXGroup;
  children = (
+ 7386749011ED15E500E5B738 /* sqFFITestFuncs.c */,
  739BEEE011C96C240093BD8A /* sq.h */,
  733EFEAC10B4D31C00A2FDA5 /* sqFFI.h */,
  73E2C0B310AA5C4700E80856 /* sqAssert.h */,
@@ -157,6 +160,7 @@
  730BD72610AA25350023C110 /* SqueakFFIPrims.c in Sources */,
  730BD72810AA26D00023C110 /* sqFFIPlugin.c in Sources */,
  458E6DD111C6D5850024C822 /* sqManualSurface.c in Sources */,
+ 7386749111ED15E500E5B738 /* sqFFITestFuncs.c in Sources */,
  );
  runOnlyForDeploymentPostprocessing = 0;
  };

Modified: branches/Cog/platforms/Cross/plugins/SqueakFFIPrims/sqFFITestFuncs.c
===================================================================
--- branches/Cog/platforms/Cross/plugins/SqueakFFIPrims/sqFFITestFuncs.c 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/platforms/Cross/plugins/SqueakFFIPrims/sqFFITestFuncs.c 2010-07-14 01:10:33 UTC (rev 2234)
@@ -6,6 +6,10 @@
 /*****************************************************************************/
 /*****************************************************************************/
 #ifndef NO_FFI_TEST
+# include "sq.h"
+
+# define LONGLONG sqLong /* should be 64 bits */
+
 typedef struct ffiTestPoint2 {
  int x;
  int y;
@@ -45,19 +49,19 @@
 /* test passing characters */
 EXPORT(char) ffiTestChars(char c1, char c2, char c3, char c4) {
  printf("4 characters came in as\nc1 = %c (%x)\nc2 = %c (%x)\nc3 = %c (%x)\nc4 = %c (%x)\n", c1, c1, c2, c2, c3, c3, c4, c4);
- return 'C';
+ return c1+c2;
 }
 
 /* test passing shorts */
 EXPORT(short) ffiTestShorts(short c1, short c2, short c3, short c4) {
  printf("4 shorts came in as\ns1 = %d (%x)\ns2 = %d (%x)\ns3 = %d (%x)\ns4 = %d (%x)\n", c1, c1, c2, c2, c3, c3, c4, c4);
- return -42;
+ return c1+c2;
 }
 
 /* test passing ints */
 EXPORT(int) ffiTestInts(int c1, int c2, int c3, int c4) {
  printf("4 ints came in as\ni1 = %d (%x)\ni2 = %d (%x)\ni3 = %d (%x)\ni4 = %d (%x)\n", c1, c1, c2, c2, c3, c3, c4, c4);
- return 42;
+ return c1+c2;
 }
 
 EXPORT(int) ffiTestInts8(int c1, int c2, int c3, int c4, int c5, int c6, int c7, int c8) {

Modified: branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile
===================================================================
--- branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile 2010-07-14 01:10:33 UTC (rev 2234)
@@ -9,7 +9,7 @@
 
 TARGET= SqueakFFIPrims$a
 
-OBJS= SqueakFFIPrims$o sqFFIPlugin$o sqManualSurface$o
+OBJS= SqueakFFIPrims$o sqFFIPlugin$o sqManualSurface$o sqFFITestFuncs$o
 
 XINCLUDES= [includes]
 

Modified: branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile.in
===================================================================
--- branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile.in 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/platforms/unix/plugins/SqueakFFIPrims/Makefile.in 2010-07-14 01:10:33 UTC (rev 2234)
@@ -9,7 +9,7 @@
 
 TARGET= SqueakFFIPrims$a
 
-OBJS= SqueakFFIPrims$o sqFFIPlugin$o sqManualSurface$o
+OBJS= SqueakFFIPrims$o sqFFIPlugin$o sqManualSurface$o sqFFITestFuncs$o
 
 XINCLUDES= [includes]
 

Modified: branches/Cog/src/plugins/Matrix2x3Plugin/Matrix2x3Plugin.c
===================================================================
--- branches/Cog/src/plugins/Matrix2x3Plugin/Matrix2x3Plugin.c 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/src/plugins/Matrix2x3Plugin/Matrix2x3Plugin.c 2010-07-14 01:10:33 UTC (rev 2234)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- VMPluginCodeGenerator VMMaker-oscog.8 uuid: b336429e-652e-4551-8d38-a00ef67eaa61
+ VMPluginCodeGenerator VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486
    from
- Matrix2x3Plugin VMMaker-oscog.8 uuid: b336429e-652e-4551-8d38-a00ef67eaa61
+ Matrix2x3Plugin VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486
  */
-static char __buildInfo[] = "Matrix2x3Plugin VMMaker-oscog.8 uuid: b336429e-652e-4551-8d38-a00ef67eaa61 " __DATE__ ;
+static char __buildInfo[] = "Matrix2x3Plugin VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486 " __DATE__ ;
 
 
 
@@ -37,7 +37,6 @@
 #include "sqMemoryAccess.h"
 
 
-
 /*** Constants ***/
 
 
@@ -76,9 +75,9 @@
 static double m23ResultY;
 static const char *moduleName =
 #ifdef SQUEAK_BUILTIN_PLUGIN
- "Matrix2x3Plugin VMMaker-oscog.8 (i)"
+ "Matrix2x3Plugin VMMaker-oscog.21 (i)"
 #else
- "Matrix2x3Plugin VMMaker-oscog.8 (e)"
+ "Matrix2x3Plugin VMMaker-oscog.21 (e)"
 #endif
 ;
 
@@ -310,8 +309,7 @@
  m3[3] = (((float) a21));
  m3[4] = (((float) a22));
  m3[5] = (((float) a23));
- interpreterProxy->pop(3);
- interpreterProxy->push(result);
+ interpreterProxy->popthenPush(3, result);
 }
 
 EXPORT(sqInt)
@@ -352,8 +350,7 @@
  interpreterProxy->primitiveFail();
  goto l2;
  }
- interpreterProxy->pop(2);
- interpreterProxy->push(interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
+ interpreterProxy->popthenPush(2, interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
  l2: /* end roundAndStoreResultPoint: */;
  }
 }
@@ -448,8 +445,7 @@
  dstOop = roundAndStoreResultRectx0y0x1y1(dstOop, minX, minY, maxX, maxY);
  }
  if (!(interpreterProxy->failed())) {
- interpreterProxy->pop(3);
- interpreterProxy->push(dstOop);
+ interpreterProxy->popthenPush(3, dstOop);
  }
 }
 
@@ -544,8 +540,7 @@
  interpreterProxy->primitiveFail();
  goto l2;
  }
- interpreterProxy->pop(2);
- interpreterProxy->push(interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
+ interpreterProxy->popthenPush(2, interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
 l2: /* end roundAndStoreResultPoint: */;
 }
 
@@ -645,8 +640,7 @@
  maxY = ((maxY < m23ResultY) ? m23ResultY : maxY);
  dstOop = roundAndStoreResultRectx0y0x1y1(dstOop, minX, minY, maxX, maxY);
  if (!(interpreterProxy->failed())) {
- interpreterProxy->pop(3);
- interpreterProxy->push(dstOop);
+ interpreterProxy->popthenPush(3, dstOop);
  }
 }
 
@@ -666,8 +660,7 @@
  && (m23ResultX <= (((double) 1073741823 ))))) {
  return interpreterProxy->primitiveFail();
  }
- interpreterProxy->pop(nItemsToPop);
- interpreterProxy->push(interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
+ interpreterProxy->popthenPush(nItemsToPop, interpreterProxy->makePointwithxValueyValue(((sqInt)m23ResultX), ((sqInt)m23ResultY)));
 }
 
 

Modified: branches/Cog/src/plugins/SqueakFFIPrims/SqueakFFIPrims.c
===================================================================
--- branches/Cog/src/plugins/SqueakFFIPrims/SqueakFFIPrims.c 2010-07-13 00:58:24 UTC (rev 2233)
+++ branches/Cog/src/plugins/SqueakFFIPrims/SqueakFFIPrims.c 2010-07-14 01:10:33 UTC (rev 2234)
@@ -1,9 +1,9 @@
 /* Automatically generated by
- VMPluginCodeGenerator * VMMaker-oscog.19 uuid: e2e1dd83-f427-4df3-a971-aababe804331
+ VMPluginCodeGenerator VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486
    from
- ReentrantIA32FFIPlugin * VMMaker-oscog.19 uuid: e2e1dd83-f427-4df3-a971-aababe804331
+ ReentrantIA32FFIPlugin VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486
  */
-static char __buildInfo[] = "ReentrantIA32FFIPlugin * VMMaker-oscog.19 uuid: e2e1dd83-f427-4df3-a971-aababe804331 " __DATE__ ;
+static char __buildInfo[] = "ReentrantIA32FFIPlugin VMMaker-oscog.21 uuid: f46d3ba4-c310-454b-9be7-30c6341f4486 " __DATE__ ;
 
 
 
@@ -173,7 +173,6 @@
 #define PrimErrBadNumArgs 5
 #define PrimErrBadReceiver 2
 #define PrimErrNoCMemory 10
-#define PrimErrUnsupported 7
 
 
 /*** Function Prototypes ***/
@@ -220,7 +219,7 @@
 static sqInt ffiPushVoidin(sqInt ignored, CalloutState *calloutState);
 static sqInt ffiReturnCStringFrom(sqInt cPointer);
 static sqInt ffiReturnPointerofTypein(usqLong retVal, sqInt retType, CalloutState *calloutState);
-static sqInt ffiReturnStructofTypein(usqLong longLongRet, sqInt ffiRetClass, CalloutState *calloutState);
+static sqInt ffiReturnStructofTypein(usqLong longLongRet, sqInt ffiRetType, CalloutState *calloutState);
 static sqInt ffiReturnType(sqInt specOnStack);
 static sqInt ffiSupportsCallingConvention(sqInt aCallingConvention);
 static sqInt ffiValidateExternalDataAtomicType(sqInt oop, sqInt atomicType);
@@ -253,6 +252,7 @@
 
 /*** Variables ***/
 static sqInt externalFunctionInstSize;
+static sqInt ffiLastError;
 static sqInt ffiLogEnabled;
 
 #ifdef SQUEAK_BUILTIN_PLUGIN
@@ -261,9 +261,9 @@
 struct VirtualMachine* interpreterProxy;
 static const char *moduleName =
 #ifdef SQUEAK_BUILTIN_PLUGIN
- "SqueakFFIPrims * VMMaker-oscog.19 (i)"
+ "SqueakFFIPrims VMMaker-oscog.21 (i)"
 #else
- "SqueakFFIPrims * VMMaker-oscog.19 (e)"
+ "SqueakFFIPrims VMMaker-oscog.21 (e)"
 #endif
 ;
 
@@ -1107,7 +1107,7 @@
     sqInt atomicType1;
     sqInt classOop;
     char *cString;
-    sqInt ffiRetClass;
+    sqInt ffiRetType;
     double floatRet;
     sqInt i;
     usqLong intRet;
@@ -1115,6 +1115,7 @@
     sqInt oop1;
     sqInt *ptr;
     sqInt retClass;
+    sqInt retClass1;
     sqInt retOop;
     sqInt retOop1;
     sqInt retType;
@@ -1150,8 +1151,8 @@
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes1 = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral1);
  retType = interpreterProxy->fetchPointerofObject(0, argTypes1);
- retClass = interpreterProxy->fetchPointerofObject(1, retType);
- if (retClass == (interpreterProxy->nilObject())) {
+ retClass1 = interpreterProxy->fetchPointerofObject(1, retType);
+ if (retClass1 == (interpreterProxy->nilObject())) {
  /* begin atomicTypeOf: */
  typeSpec1 = (calloutState->ffiRetHeader);
  atomicType1 = ((usqInt) (typeSpec1 & FFIAtomicTypeMask)) >> FFIAtomicTypeShift;
@@ -1190,7 +1191,7 @@
  interpreterProxy->storePointerofObjectwithValue(1, retOop1, oop1);
  return interpreterProxy->methodReturnValue(retOop1);
  }
- interpreterProxy->pushRemappableOop(retClass);
+ interpreterProxy->pushRemappableOop(retClass1);
  if (((calloutState->ffiRetHeader)) & FFIFlagStructure) {
  classOop = interpreterProxy->classByteArray();
  }
@@ -1203,9 +1204,9 @@
 
  /* return class */
 
- retClass = interpreterProxy->popRemappableOop();
+ retClass1 = interpreterProxy->popRemappableOop();
  interpreterProxy->pushRemappableOop(oop1);
- retOop1 = interpreterProxy->instantiateClassindexableSize(retClass, 0);
+ retOop1 = interpreterProxy->instantiateClassindexableSize(retClass1, 0);
 
  /* external address */
 
@@ -1220,8 +1221,9 @@
  ? interpreterProxy->stackValue(1)
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral);
- ffiRetClass = interpreterProxy->fetchPointerofObject(0, argTypes);
- retOop = interpreterProxy->instantiateClassindexableSize(ffiRetClass, 0);
+ ffiRetType = interpreterProxy->fetchPointerofObject(0, argTypes);
+ retClass = interpreterProxy->fetchPointerofObject(1, ffiRetType);
+ retOop = interpreterProxy->instantiateClassindexableSize(retClass, 0);
  interpreterProxy->pushRemappableOop(retOop);
  oop = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classByteArray(), (calloutState->structReturnSize));
  if (returnStructInRegisters((calloutState->structReturnSize))) {
@@ -1265,7 +1267,7 @@
     sqInt classOop;
     char *cString;
     sqInt err;
-    sqInt ffiRetClass;
+    sqInt ffiRetType;
     sqInt flags;
     double floatRet;
     sqInt functionName;
@@ -1281,6 +1283,7 @@
     sqInt requiredStackSize;
     sqInt result;
     sqInt retClass;
+    sqInt retClass1;
     sqInt retOop;
     sqInt retOop1;
     sqInt retType;
@@ -1392,7 +1395,8 @@
  (calloutState->currentArg = allocation + 0);
  (calloutState->limit = (allocation + stackSize) + 0);
  if ((((calloutState->structReturnSize)) > 0)
- && (1)) {
+ && (1
+ && (!(returnStructInRegisters((calloutState->structReturnSize)))))) {
  /* begin ffiPushPointer:in: */
  pointer = (calloutState->limit);
  if ((((calloutState->currentArg)) + 4) > ((calloutState->limit))) {
@@ -1458,8 +1462,8 @@
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes1 = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral1);
  retType = interpreterProxy->fetchPointerofObject(0, argTypes1);
- retClass = interpreterProxy->fetchPointerofObject(1, retType);
- if (retClass == (interpreterProxy->nilObject())) {
+ retClass1 = interpreterProxy->fetchPointerofObject(1, retType);
+ if (retClass1 == (interpreterProxy->nilObject())) {
  /* begin atomicTypeOf: */
  typeSpec1 = (calloutState->ffiRetHeader);
  atomicType1 = ((usqInt) (typeSpec1 & FFIAtomicTypeMask)) >> FFIAtomicTypeShift;
@@ -1501,7 +1505,7 @@
  result = interpreterProxy->methodReturnValue(retOop1);
  goto l5;
  }
- interpreterProxy->pushRemappableOop(retClass);
+ interpreterProxy->pushRemappableOop(retClass1);
  if (((calloutState->ffiRetHeader)) & FFIFlagStructure) {
  classOop = interpreterProxy->classByteArray();
  }
@@ -1514,9 +1518,9 @@
 
  /* return class */
 
- retClass = interpreterProxy->popRemappableOop();
+ retClass1 = interpreterProxy->popRemappableOop();
  interpreterProxy->pushRemappableOop(oop1);
- retOop1 = interpreterProxy->instantiateClassindexableSize(retClass, 0);
+ retOop1 = interpreterProxy->instantiateClassindexableSize(retClass1, 0);
 
  /* external address */
 
@@ -1532,8 +1536,9 @@
  ? interpreterProxy->stackValue(1)
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral);
- ffiRetClass = interpreterProxy->fetchPointerofObject(0, argTypes);
- retOop = interpreterProxy->instantiateClassindexableSize(ffiRetClass, 0);
+ ffiRetType = interpreterProxy->fetchPointerofObject(0, argTypes);
+ retClass = interpreterProxy->fetchPointerofObject(1, ffiRetType);
+ retOop = interpreterProxy->instantiateClassindexableSize(retClass, 0);
  interpreterProxy->pushRemappableOop(retOop);
  oop2 = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classByteArray(), (calloutState->structReturnSize));
  if (returnStructInRegisters((calloutState->structReturnSize))) {
@@ -1567,7 +1572,6 @@
 static sqInt
 ffiCheckReturnWithin(sqInt retSpec, sqInt retClass, CalloutState *calloutState) {
     sqInt ffiRetSpec;
-    sqInt returnStructSize;
 
  if (!(retClass == (interpreterProxy->nilObject()))) {
  if (!(interpreterProxy->includesBehaviorThatOf(retClass, interpreterProxy->classExternalStructure()))) {
@@ -1587,11 +1591,8 @@
  return FFIErrorBadReturn;
  }
  }
- if ((((calloutState->ffiRetHeader)) & (FFIFlagPointer || FFIFlagStructure)) == FFIFlagStructure) {
- returnStructSize = ((calloutState->ffiRetHeader)) & FFIStructSizeMask;
- if (!(returnStructInRegisters(returnStructSize))) {
- (calloutState->structReturnSize = returnStructSize);
- }
+ if ((((calloutState->ffiRetHeader)) & (FFIFlagPointer | FFIFlagStructure)) == FFIFlagStructure) {
+ (calloutState->structReturnSize = ((calloutState->ffiRetHeader)) & FFIStructSizeMask);
  }
  return 0;
 }
@@ -1679,14 +1680,11 @@
  size + 2 maps them to
  size of table + 1 on up. This OFFSET IS undone by ExternalFunction
  class>>externalCallFailedWith:. Thus we can communicate back both
- PrimErr.. and FFIError codes. Complex but necessary.
- Do not record the error code because as yet there is no per-process
- mechanism to do this, and since
- the error is accessible through the primitive errror code there is no
- need.  */
+ PrimErr.. and FFIError codes. Complex but necessary. */
 
 static sqInt
 ffiFail(sqInt reason) {
+ ffiLastError = reason;
  return interpreterProxy->primitiveFailFor((reason >= FFINoCalloutAvailable
  ? (reason + 2) + (interpreterProxy->slotSizeOf(interpreterProxy->primitiveErrorTable()))
  : -reason));
@@ -2480,11 +2478,13 @@
  alloca'ed space pointed to by the calloutState. */
 
 static sqInt
-ffiReturnStructofTypein(usqLong longLongRet, sqInt ffiRetClass, CalloutState *calloutState) {
+ffiReturnStructofTypein(usqLong longLongRet, sqInt ffiRetType, CalloutState *calloutState) {
     sqInt oop;
+    sqInt retClass;
     sqInt retOop;
 
- retOop = interpreterProxy->instantiateClassindexableSize(ffiRetClass, 0);
+ retClass = interpreterProxy->fetchPointerofObject(1, ffiRetType);
+ retOop = interpreterProxy->instantiateClassindexableSize(retClass, 0);
  interpreterProxy->pushRemappableOop(retOop);
  oop = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classByteArray(), (calloutState->structReturnSize));
  if (returnStructInRegisters((calloutState->structReturnSize))) {
@@ -2666,7 +2666,7 @@
     char *cString;
     sqInt err;
     sqInt externalFunction;
-    sqInt ffiRetClass;
+    sqInt ffiRetType;
     sqInt flags;
     double floatRet;
     sqInt functionName;
@@ -2684,6 +2684,7 @@
     sqInt requiredStackSize;
     sqInt result;
     sqInt retClass;
+    sqInt retClass1;
     sqInt retOop;
     sqInt retOop1;
     sqInt retType;
@@ -2808,7 +2809,8 @@
  (calloutState->currentArg = allocation + 0);
  (calloutState->limit = (allocation + stackSize) + 0);
  if ((((calloutState->structReturnSize)) > 0)
- && (1)) {
+ && (1
+ && (!(returnStructInRegisters((calloutState->structReturnSize)))))) {
  /* begin ffiPushPointer:in: */
  pointer = (calloutState->limit);
  if ((((calloutState->currentArg)) + 4) > ((calloutState->limit))) {
@@ -2875,8 +2877,8 @@
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes1 = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral1);
  retType = interpreterProxy->fetchPointerofObject(0, argTypes1);
- retClass = interpreterProxy->fetchPointerofObject(1, retType);
- if (retClass == (interpreterProxy->nilObject())) {
+ retClass1 = interpreterProxy->fetchPointerofObject(1, retType);
+ if (retClass1 == (interpreterProxy->nilObject())) {
  /* begin atomicTypeOf: */
  typeSpec1 = (calloutState->ffiRetHeader);
  atomicType1 = ((usqInt) (typeSpec1 & FFIAtomicTypeMask)) >> FFIAtomicTypeShift;
@@ -2918,7 +2920,7 @@
  result = interpreterProxy->methodReturnValue(retOop1);
  goto l6;
  }
- interpreterProxy->pushRemappableOop(retClass);
+ interpreterProxy->pushRemappableOop(retClass1);
  if (((calloutState->ffiRetHeader)) & FFIFlagStructure) {
  classOop = interpreterProxy->classByteArray();
  }
@@ -2931,9 +2933,9 @@
 
  /* return class */
 
- retClass = interpreterProxy->popRemappableOop();
+ retClass1 = interpreterProxy->popRemappableOop();
  interpreterProxy->pushRemappableOop(oop1);
- retOop1 = interpreterProxy->instantiateClassindexableSize(retClass, 0);
+ retOop1 = interpreterProxy->instantiateClassindexableSize(retClass1, 0);
 
  /* external address */
 
@@ -2949,8 +2951,9 @@
  ? interpreterProxy->stackValue(1)
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral);
- ffiRetClass = interpreterProxy->fetchPointerofObject(0, argTypes);
- retOop = interpreterProxy->instantiateClassindexableSize(ffiRetClass, 0);
+ ffiRetType = interpreterProxy->fetchPointerofObject(0, argTypes);
+ retClass = interpreterProxy->fetchPointerofObject(1, ffiRetType);
+ retOop = interpreterProxy->instantiateClassindexableSize(retClass, 0);
  interpreterProxy->pushRemappableOop(retOop);
  oop2 = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classByteArray(), (calloutState->structReturnSize));
  if (returnStructInRegisters((calloutState->structReturnSize))) {
@@ -3003,7 +3006,7 @@
     char *cString;
     sqInt err;
     sqInt externalFunction;
-    sqInt ffiRetClass;
+    sqInt ffiRetType;
     sqInt flags;
     double floatRet;
     sqInt functionName;
@@ -3020,6 +3023,7 @@
     sqInt requiredStackSize;
     sqInt result;
     sqInt retClass;
+    sqInt retClass1;
     sqInt retOop;
     sqInt retOop1;
     sqInt retType;
@@ -3147,7 +3151,8 @@
  (calloutState->currentArg = allocation + 0);
  (calloutState->limit = (allocation + stackSize) + 0);
  if ((((calloutState->structReturnSize)) > 0)
- && (1)) {
+ && (1
+ && (!(returnStructInRegisters((calloutState->structReturnSize)))))) {
  /* begin ffiPushPointer:in: */
  pointer = (calloutState->limit);
  if ((((calloutState->currentArg)) + 4) > ((calloutState->limit))) {
@@ -3214,8 +3219,8 @@
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes1 = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral1);
  retType = interpreterProxy->fetchPointerofObject(0, argTypes1);
- retClass = interpreterProxy->fetchPointerofObject(1, retType);
- if (retClass == (interpreterProxy->nilObject())) {
+ retClass1 = interpreterProxy->fetchPointerofObject(1, retType);
+ if (retClass1 == (interpreterProxy->nilObject())) {
  /* begin atomicTypeOf: */
  typeSpec1 = (calloutState->ffiRetHeader);
  atomicType1 = ((usqInt) (typeSpec1 & FFIAtomicTypeMask)) >> FFIAtomicTypeShift;
@@ -3257,7 +3262,7 @@
  result = interpreterProxy->methodReturnValue(retOop1);
  goto l6;
  }
- interpreterProxy->pushRemappableOop(retClass);
+ interpreterProxy->pushRemappableOop(retClass1);
  if (((calloutState->ffiRetHeader)) & FFIFlagStructure) {
  classOop = interpreterProxy->classByteArray();
  }
@@ -3270,9 +3275,9 @@
 
  /* return class */
 
- retClass = interpreterProxy->popRemappableOop();
+ retClass1 = interpreterProxy->popRemappableOop();
  interpreterProxy->pushRemappableOop(oop1);
- retOop1 = interpreterProxy->instantiateClassindexableSize(retClass, 0);
+ retOop1 = interpreterProxy->instantiateClassindexableSize(retClass1, 0);
 
  /* external address */
 
@@ -3288,8 +3293,9 @@
  ? interpreterProxy->stackValue(1)
  : interpreterProxy->literalofMethod(0, interpreterProxy->primitiveMethod()));
  argTypes = interpreterProxy->fetchPointerofObject(ExternalFunctionArgTypesIndex, specLiteral);
- ffiRetClass = interpreterProxy->fetchPointerofObject(0, argTypes);
- retOop = interpreterProxy->instantiateClassindexableSize(ffiRetClass, 0);
+ ffiRetType = interpreterProxy->fetchPointerofObject(0, argTypes);
+ retClass = interpreterProxy->fetchPointerofObject(1, ffiRetType);
+ retOop = interpreterProxy->instantiateClassindexableSize(retClass, 0);
  interpreterProxy->pushRemappableOop(retOop);
  oop2 = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classByteArray(), (calloutState->structReturnSize));
  if (returnStructInRegisters((calloutState->structReturnSize))) {
@@ -3404,8 +3410,7 @@
  oop = interpreterProxy->instantiateClassindexableSize(interpreterProxy->classExternalAddress(), 4);
  ptr = interpreterProxy->firstIndexableField(oop);
  ptr[0] = addr;
- interpreterProxy->pop(2);
- return interpreterProxy->push(oop);
+ interpreterProxy->popthenPush(2, oop);
 }
 
 
@@ -3462,8 +3467,7 @@
  }
  ((int*)addr)[0] = ((int*)(&floatValue))[0];
  ((int*)addr)[1] = ((int*)(&floatValue))[1];
- interpreterProxy->pop(3);
- return interpreterProxy->push(floatOop);
+ interpreterProxy->popthenPush(3, floatOop);
 }
 
 
@@ -3518,8 +3522,7 @@
  return 0;
  }
  ((int*)addr)[0] = ((int*)(&floatValue))[0];
- interpreterProxy->pop(3);
- return interpreterProxy->push(floatOop);
+ interpreterProxy->popthenPush(3, floatOop);
 }
 
 
@@ -3557,12 +3560,14 @@
 
 /* Primitive. Return the error code from a failed call to the foreign
  function interface.
- Always fail. In the thread-enabled FFI access errors via the primitive
- error code. */
+ This is for backwards-compatibility. Thread-safe access to the error code
+ is via the
+ primitive error code. */
 
 EXPORT(sqInt)
 primitiveFFIGetLastError(void) {
- return interpreterProxy->primitiveFailFor(PrimErrUnsupported);
+ interpreterProxy->pop(1);
+ return interpreterProxy->pushInteger(ffiLastError);
 }
 
 
@@ -3619,15 +3624,11 @@
  /* general 32 bit integer */
 
  value = longAt(addr);
- if (isSigned) {
- value = interpreterProxy->signed32BitIntegerFor(value);
- }
- else {
- value = interpreterProxy->positive32BitIntegerFor(value);
- }
+ value = (isSigned
+ ? interpreterProxy->signed32BitIntegerFor(value)
+ : interpreterProxy->positive32BitIntegerFor(value));
  }
- interpreterProxy->pop(4);
- return interpreterProxy->push(value);
+ interpreterProxy->popthenPush(4, value);
 }
 
 
@@ -3696,8 +3697,7 @@
  else {
  longAtput(addr, value);
  }
- interpreterProxy->pop(5);
- return interpreterProxy->push(valueOop);
+ interpreterProxy->popthenPush(5, valueOop);
 }