<div dir="ltr">Thanks Nicolas!  And great that you found slips.  The more eyes the merrier.</div><div class="gmail_extra"><br><div class="gmail_quote">On Fri, Mar 4, 2016 at 5:24 PM,  <span dir="ltr">&lt;<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:<br>
<a href="http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1711.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/VMMaker/VMMaker.oscog-nice.1711.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-nice.1711<br>
Author: nice<br>
Time: 5 March 2016, 2:14:57.11 am<br>
UUID: 9e7ba417-b6ed-4263-82f2-27ec641d8f30<br>
Ancestors: VMMaker.oscog-eem.1709<br>
<br>
3 minor fixes for type inference:<br>
1) remove unecessary block argument assignment<br>
2) infer type of allMask:<br>
3) infer type of rem: instead of mod: (mod: does not exist)<br>
<br>
Don&#39;t use cCode: pointer aliasing for storing/fetching float/double in FFI primitives.<br>
Replace with a call to mem:cp:y:<br>
- the first one is dangerous with modern C compilers<br>
- while the second is optimized away (no call to memcpy)<br>
<br>
=============== Diff against VMMaker.oscog-eem.1709 ===============<br>
<br>
Item was changed:<br>
  ----- Method: FFIPlugin&gt;&gt;primitiveFFIDoubleAt (in category &#39;primitives&#39;) -----<br>
  primitiveFFIDoubleAt<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #double&gt;<br>
-       &lt;var: #floatValue type:&#39;double &#39;&gt;<br>
        byteOffset := interpreterProxy stackIntegerValue: 0.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[0] = ((int*)addr)[0]&#39;.<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[1] = ((int*)addr)[1]&#39;.<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: FFIPlugin&gt;&gt;primitiveFFIDoubleAtPut (in category &#39;primitives&#39;) -----<br>
  primitiveFFIDoubleAtPut<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue floatOop |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #double&gt;<br>
-       &lt;var: #floatValue type:&#39;double &#39;&gt;<br>
        floatOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: floatOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:&#39;double&#39;]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:&#39;double&#39;].<br>
        byteOffset := interpreterProxy stackIntegerValue: 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)addr)[0] = ((int*)(&amp;floatValue))[0]&#39;.<br>
-       self cCode:&#39;((int*)addr)[1] = ((int*)(&amp;floatValue))[1]&#39;.<br>
        interpreterProxy pop: 3.<br>
        ^interpreterProxy push: floatOop!<br>
<br>
Item was changed:<br>
  ----- Method: FFIPlugin&gt;&gt;primitiveFFIFloatAt (in category &#39;primitives&#39;) -----<br>
  primitiveFFIFloatAt<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #float&gt;<br>
-       &lt;var: #floatValue type:&#39;float &#39;&gt;<br>
        byteOffset := interpreterProxy stackIntegerValue: 0.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[0] = ((int*)addr)[0]&#39;.<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue!<br>
<br>
Item was changed:<br>
  ----- Method: FFIPlugin&gt;&gt;primitiveFFIFloatAtPut (in category &#39;primitives&#39;) -----<br>
  primitiveFFIFloatAtPut<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue floatOop |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #float&gt;<br>
-       &lt;var: #floatValue type:&#39;float &#39;&gt;<br>
        floatOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: floatOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:&#39;float&#39;]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:&#39;float&#39;].<br>
        byteOffset := interpreterProxy stackIntegerValue: 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)addr)[0] = ((int*)(&amp;floatValue))[0]&#39;.<br>
        interpreterProxy pop: 3.<br>
        ^interpreterProxy push: floatOop!<br>
<br>
Item was changed:<br>
  ----- Method: IA32ABIPlugin&gt;&gt;primDoubleAt (in category &#39;primitives-accessing&#39;) -----<br>
  primDoubleAt<br>
        &quot;Answer the 64-bit double starting at the given byte offset (little endian).&quot;<br>
        &quot;&lt;Alien&gt; doubleAt: index &lt;Integer&gt; ^&lt;Float&gt;<br>
                &lt;primitive: &#39;primDoubleAt&#39; error: errorCode module: &#39;IA32ABI&#39;&gt;&quot;<br>
        | byteOffset rcvr startAddr addr floatValue |<br>
        &lt;export: true&gt;<br>
+       &lt;var: #floatValue type: #double&gt;<br>
-       &lt;var: #floatValue type:&#39;double &#39;&gt;<br>
<br>
        byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadArgument].<br>
        (self index: byteOffset length: 8 inRange: rcvr) ifFalse:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadIndex].<br>
        (startAddr := self startOfData: rcvr) = 0 ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadReceiver].<br>
        addr := startAddr + byteOffset.<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((long *)(&amp;floatValue))[0] = ((long *)addr)[0]; ((long *)(&amp;floatValue))[1] = ((long *)addr)[1]&#39;<br>
-               inSmalltalk: [floatValue := rcvr doubleAt: byteOffset].<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue!<br>
<br>
Item was changed:<br>
  ----- Method: IA32ABIPlugin&gt;&gt;primDoubleAtPut (in category &#39;primitives-accessing&#39;) -----<br>
  primDoubleAtPut<br>
        &quot;Store a double into 64 bits starting at the given byte offset (little endian).&quot;<br>
        &quot;&lt;Alien&gt; doubleAt: index &lt;Integer&gt; put: value &lt;Float | Integer&gt; ^&lt;Float | Integer&gt;<br>
                &lt;primitive: &#39;primDoubleAtPut&#39; error: errorCode module: &#39;IA32ABI&#39;&gt;&quot;<br>
        | byteOffset rcvr startAddr addr valueOop floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;var: #floatValue type: #double&gt;<br>
<br>
        valueOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: valueOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].<br>
        byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadArgument].<br>
        (self index: byteOffset length: 8 inRange: rcvr) ifFalse:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadIndex].<br>
        (interpreterProxy isOopImmutable: rcvr) ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrNoModification].<br>
        (startAddr := self startOfData: rcvr) = 0 ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadReceiver].<br>
        addr := startAddr + byteOffset.<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)addr)[0] = ((int*)(&amp;floatValue))[0]&#39;.<br>
-       self cCode:&#39;((int*)addr)[1] = ((int*)(&amp;floatValue))[1]&#39;.<br>
        interpreterProxy methodReturnValue: valueOop!<br>
<br>
Item was changed:<br>
  ----- Method: IA32ABIPlugin&gt;&gt;primFloatAt (in category &#39;primitives-accessing&#39;) -----<br>
  primFloatAt<br>
        &quot;Answer the 32-bit float starting at the given byte offset (little endian).&quot;<br>
        &quot;&lt;Alien&gt; floatAt: index &lt;Integer&gt; ^&lt;Float&gt;<br>
                &lt;primitive: &#39;primFloatAt&#39; error: errorCode module: &#39;IA32ABI&#39;&gt;&quot;<br>
        | byteOffset rcvr startAddr addr floatValue |<br>
        &lt;export: true&gt;<br>
+       &lt;var: #floatValue type: #float&gt;<br>
-       &lt;var: #floatValue type: &#39;float &#39;&gt;<br>
<br>
        byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 0) - 1.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadArgument].<br>
        (self index: byteOffset length: 4 inRange: rcvr) ifFalse:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadIndex].<br>
        (startAddr := self startOfData: rcvr) = 0 ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadReceiver].<br>
        addr := startAddr + byteOffset.<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((long *)(&amp;floatValue))[0] = ((long *)addr)[0]&#39;<br>
-               inSmalltalk: [floatValue := rcvr floatAt: byteOffset].<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue!<br>
<br>
Item was changed:<br>
  ----- Method: IA32ABIPlugin&gt;&gt;primFloatAtPut (in category &#39;primitives-accessing&#39;) -----<br>
  primFloatAtPut<br>
        &quot;Store a float into 32 bits starting at the given byte offset (little endian).&quot;<br>
        &quot;&lt;Alien&gt; floatAt: index &lt;Integer&gt; put: value &lt;Float | Integer&gt; ^&lt;Float | Integer&gt;<br>
                &lt;primitive: &#39;primFloatAtPut&#39; error: errorCode module: &#39;IA32ABI&#39;&gt;&quot;<br>
        | byteOffset rcvr startAddr addr valueOop floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;var: #floatValue type: #float&gt;<br>
<br>
        valueOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: valueOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: valueOop) to: #double]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: valueOop) to: #double].<br>
        byteOffset := (interpreterProxy stackPositiveMachineIntegerValue: 1) - 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadArgument].<br>
        (self index: byteOffset length: 4 inRange: rcvr) ifFalse:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadIndex].<br>
        (interpreterProxy isOopImmutable: rcvr) ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrNoModification].<br>
        (startAddr := self startOfData: rcvr) = 0 ifTrue:<br>
                [^interpreterProxy primitiveFailFor: PrimErrBadReceiver].<br>
        addr := startAddr + byteOffset.<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((long *)addr)[0] = ((long *)(&amp;floatValue))[0]&#39;.<br>
        interpreterProxy methodReturnValue: valueOop!<br>
<br>
Item was changed:<br>
  ----- Method: TMethod&gt;&gt;addTypesFor:to:in: (in category &#39;type inference&#39;) -----<br>
  addTypesFor: node to: typeSet in: aCodeGen<br>
        &quot;Add the value tupes for the node to typeSet.<br>
         Answer if any type was derived from an as-yet-untyped method, which allows us to abort<br>
         inferReturnTypeFromReturnsIn: if the return type depends on a yet-to-be-typed method.&quot;<br>
        | expr |<br>
        expr := node.<br>
        [expr isAssignment or: [expr isStmtList]] whileTrue:<br>
                [expr isAssignment ifTrue:<br>
                        [expr := expr variable].<br>
                 expr isStmtList ifTrue:<br>
                        [expr := expr statements last]].<br>
        expr isSend ifTrue:<br>
                [(#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:) includes: expr selector) ifTrue:<br>
                        [^expr args<br>
                                inject: false<br>
                                into: [:asYetUntyped :block|<br>
+                                       asYetUntyped | (self addTypesFor: block to: typeSet in: aCodeGen)]].<br>
+                (#(= ~= == ~~ &lt; &gt; &lt;= &gt;= anyMask: allMask: noMask:) includes: expr selector) ifTrue:<br>
-                                       asYetUntyped := asYetUntyped | (self addTypesFor: block to: typeSet in: aCodeGen)]].<br>
-                (#(= ~= == ~~ &lt; &gt; &lt;= &gt;= anyMask: noMask:) includes: expr selector) ifTrue:<br>
                        [typeSet add: #sqInt. ^false].<br>
+                (#(+ - * / // \\ rem: quo: bitAnd: bitClear: bitOr: bitXor: bitShift:) includes: expr selector) ifTrue:<br>
-                (#(+ - * / // \\ mod: quo: bitAnd: bitClear: bitOr: bitXor: bitShift:) includes: expr selector) ifTrue:<br>
                        [| types |<br>
                         types := Set new.<br>
                         self addTypesFor: expr receiver to: types in: aCodeGen.<br>
                         (types size = 1 and: [types anyOne last = $*]) ifTrue: &quot;pointer arithmetic&quot;<br>
                                [typeSet add: types anyOne. ^false].<br>
                         self addTypesFor: expr args first to: types in: aCodeGen.<br>
                         types := aCodeGen harmonizeReturnTypesIn: types.<br>
                         types size = 2 ifTrue:<br>
                                [(types includes: #double) ifTrue:<br>
                                        [typeSet add: #double. ^false].<br>
                                 (types includes: #float) ifTrue:<br>
                                        [typeSet add: #float. ^false].<br>
                                ^false]. &quot;don&#39;t know; leave unspecified.&quot;<br>
                        types notEmpty ifTrue:<br>
                                [typeSet add: types anyOne].<br>
                        ^false].<br>
                &quot;Abort only for untyped methods that will be typed, but don&#39;t be phased by recursion.&quot;<br>
                 ^(aCodeGen returnTypeForSend: expr in: self)<br>
                        ifNotNil: [:type| typeSet add: type. false]<br>
                        ifNil: [(aCodeGen methodNamed: expr selector) notNil and: [expr selector ~~ selector]]].<br>
        expr isVariable ifTrue:<br>
                [(aCodeGen typeOfVariable: expr name)<br>
                        ifNotNil: [:type| typeSet add: type]<br>
                        ifNil: [typeSet add: (expr name = &#39;self&#39;<br>
                                                                                ifTrue: [#void]<br>
                                                                                ifFalse: [#sqInt])]].<br>
        expr isConstant ifTrue:<br>
                [| val |<br>
                 val := expr value.<br>
                 val isInteger ifTrue:<br>
                        [typeSet add: ((val &gt;= 0 ifTrue: [val] ifFalse: [-1 - val]) highBit &lt;= 32<br>
                                                                        ifTrue: [#sqInt]<br>
                                                                        ifFalse: [#sqLong])].<br>
                 (#(nil true false) includes: val) ifTrue:<br>
                        [typeSet add: #sqInt].<br>
                 val isFloat ifTrue:<br>
                        [typeSet add: #float]].<br>
        ^false!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin&gt;&gt;primitiveFFIDoubleAt (in category &#39;primitives&#39;) -----<br>
  primitiveFFIDoubleAt<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #double&gt;<br>
-       &lt;var: #floatValue type:&#39;double &#39;&gt;<br>
        byteOffset := interpreterProxy stackIntegerValue: 0.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[0] = ((int*)addr)[0]&#39;.<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[1] = ((int*)addr)[1]&#39;.<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue<br>
  !<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin&gt;&gt;primitiveFFIDoubleAtPut (in category &#39;primitives&#39;) -----<br>
  primitiveFFIDoubleAtPut<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue floatOop |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #double&gt;<br>
-       &lt;var: #floatValue type:&#39;double &#39;&gt;<br>
        floatOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: floatOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:&#39;double&#39;]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:&#39;double&#39;].<br>
        byteOffset := interpreterProxy stackIntegerValue: 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 8.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)addr)[0] = ((int*)(&amp;floatValue))[0]&#39;.<br>
-       self cCode:&#39;((int*)addr)[1] = ((int*)(&amp;floatValue))[1]&#39;.<br>
        ^interpreterProxy pop: 3 thenPush: floatOop!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin&gt;&gt;primitiveFFIFloatAt (in category &#39;primitives&#39;) -----<br>
  primitiveFFIFloatAt<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #float&gt;<br>
-       &lt;var: #floatValue type:&#39;float &#39;&gt;<br>
        byteOffset := interpreterProxy stackIntegerValue: 0.<br>
        rcvr := interpreterProxy stackObjectValue: 1.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: (self addressOf: floatValue) cp: addr y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)(&amp;floatValue))[0] = ((int*)addr)[0]&#39;.<br>
        interpreterProxy pop: 2.<br>
        ^interpreterProxy pushFloat: floatValue!<br>
<br>
Item was changed:<br>
  ----- Method: ThreadedFFIPlugin&gt;&gt;primitiveFFIFloatAtPut (in category &#39;primitives&#39;) -----<br>
  primitiveFFIFloatAtPut<br>
        &quot;Return a (signed or unsigned) n byte integer from the given byte offset.&quot;<br>
        | byteOffset rcvr addr floatValue floatOop |<br>
        &lt;export: true&gt;<br>
        &lt;inline: false&gt;<br>
+       &lt;var: #floatValue type: #float&gt;<br>
-       &lt;var: #floatValue type:&#39;float &#39;&gt;<br>
        floatOop := interpreterProxy stackValue: 0.<br>
        (interpreterProxy isIntegerObject: floatOop)<br>
                ifTrue:[floatValue := self cCoerce: (interpreterProxy integerValueOf: floatOop) to:&#39;float&#39;]<br>
                ifFalse:[floatValue := self cCoerce: (interpreterProxy floatValueOf: floatOop) to:&#39;float&#39;].<br>
        byteOffset := interpreterProxy stackIntegerValue: 1.<br>
        rcvr := interpreterProxy stackObjectValue: 2.<br>
        interpreterProxy failed ifTrue:[^0].<br>
        addr := self ffiAddressOf: rcvr startingAt: byteOffset size: 4.<br>
        interpreterProxy failed ifTrue:[^0].<br>
+       self mem: addr cp: (self addressOf: floatValue) y: (self sizeof: floatValue).<br>
-       self cCode:&#39;((int*)addr)[0] = ((int*)(&amp;floatValue))[0]&#39;.<br>
        ^interpreterProxy pop: 3 thenPush: floatOop!<br>
<br>
</blockquote></div><br><br clear="all"><div><br></div>-- <br><div class="gmail_signature"><div dir="ltr"><div><span style="font-size:small;border-collapse:separate"><div>_,,,^..^,,,_<br></div><div>best, Eliot</div></span></div></div></div>
</div>