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

Nicolas Cellier nicolas.cellier.aka.nice at gmail.com
Tue Aug 27 02:14:40 UTC 2019


Hi Eliot,

Le mar. 27 août 2019 à 01:09, Eliot Miranda <eliot.miranda at gmail.com> a
écrit :

>
> Nicolas,
>
>     thanks!  Great work!  I completely missed this issue.  Can I check my
> understanding?  If the VM is comparing a SmallInteger against a Float where
> the SmallInteger has more significant digits than the Float (i.e. the Float
> has no fraction part and is greater than 2^52 (?)) the VM must coerce the
> Float to an integer and compare in the integer realm.  If not, then it is
> safe for the VM to coerce the integer to a float and compare in the
> floating-point realm.  Do I have this right?
>

I explained it in details in
https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/417

We know that conversion int -> float is monotonic
thus: someInt < someFloat => someInt asFloat <= someFloat.
and: someInt > someFloat => someInt asFloat >= someFloat

inversely: someInt asFloat < someFloat => someInt < someFloat
and: someInt asFloat > someFloat => someInt > someFloat

The only case of ambiguity is when someInt asFloat = someFloat because
someInt could have been rounded upper or lower...
In every other case, we are safe to convert someInt asFloat and compare the
floats.

In case of ambiguity, we usually compare someInt and someFloat
asTrueFraction at image side.
But here, we know that someFloat = someInt asFloat.
someInt asFloat cannot have a fraction part, so someFloat neither.
So we could compare someInt and someFloat asInteger at image side.
And we can also safely compare someInt and (int64) someFloat in
bounded-C-world without fear of overflow and undefined behaviour thanks to
the guard tag bits.

This way, no need to let the primitiveFail and handle fallback at image
side, we can perform all the simple operations at VM side and still have
exact operations :)


> On Wed, Aug 21, 2019 at 3:29 PM <commits at source.squeak.org> wrote:
>
>>
>> Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
>> http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2541.mcz
>>
>> ==================== Summary ====================
>>
>> Name: VMMaker.oscog-nice.2541
>> Author: nice
>> Time: 22 August 2019, 12:26:47.657132 am
>> UUID: 7141fb7c-1789-49e3-8a91-d1bc5195b727
>> Ancestors: VMMaker.oscog-nice.2540
>>
>> Partial fix - Part 4 - for bug
>> https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/417
>>
>> Fix my stupid bug of part 3.
>> Too many if level for such late time :(
>>
>> =============== Diff against VMMaker.oscog-nice.2539 ===============
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatEqual (in
>> category 'arithmetic float primitives') -----
>>   primitiveSmallFloatEqual
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue:
>> +                                       ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: rcvr
>> asInteger = intArg]
>> +                               ifFalse: [self pop: 2 thenPushBool: rcvr
>> = arg]]
>> +                       ifFalse: [self pop: 2 thenPushBool: rcvr = arg]]!
>> -               [self pop: 2 thenPushBool: rcvr = arg]!
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterOrEqual
>> (in category 'arithmetic float primitives') -----
>>   primitiveSmallFloatGreaterOrEqual
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue:
>> +                                       ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: rcvr
>> asInteger >= intArg]
>> +                               ifFalse: [self pop: 2 thenPushBool: rcvr
>> >= arg]]
>> +                       ifFalse: [self pop: 2 thenPushBool: rcvr >= arg]]!
>> -               [self pop: 2 thenPushBool: rcvr >= arg]!
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatGreaterThan (in
>> category 'arithmetic float primitives') -----
>>   primitiveSmallFloatGreaterThan
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue:
>> +                                       ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: rcvr
>> asInteger > intArg]
>> +                               ifFalse: [self pop: 2 thenPushBool: rcvr
>> > arg]]
>> +                       ifFalse: [self pop: 2 thenPushBool: rcvr > arg]]!
>> -               [self pop: 2 thenPushBool: rcvr > arg]!
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessOrEqual (in
>> category 'arithmetic float primitives') -----
>>   primitiveSmallFloatLessOrEqual
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue:
>> +                                       ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: rcvr
>> asInteger <= intArg]
>> +                               ifFalse: [self pop: 2 thenPushBool: rcvr
>> <= arg]]
>> +                       ifFalse: [self pop: 2 thenPushBool: rcvr <= arg]]!
>> -               [self pop: 2 thenPushBool: rcvr <= arg]!
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatLessThan (in
>> category 'arithmetic float primitives') -----
>>   primitiveSmallFloatLessThan
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue:
>> +                                       ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: rcvr
>> asInteger < intArg]
>> +                               ifFalse: [self pop: 2 thenPushBool: rcvr
>> < arg]]
>> +                       ifFalse: [self pop: 2 thenPushBool: rcvr < arg]]!
>> -               [self pop: 2 thenPushBool: rcvr < arg]!
>>
>> Item was changed:
>>   ----- Method: InterpreterPrimitives>>primitiveSmallFloatNotEqual (in
>> category 'arithmetic float primitives') -----
>>   primitiveSmallFloatNotEqual
>>         <option: #Spur64BitMemoryManager>
>> +       | rcvr arg intArg |
>> -       | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory smallFloatValueOf: (self stackValue: 1).
>>         arg := objectMemory loadFloatOrIntFrom: self stackTop.
>>         self successful ifTrue:
>> +               [self cppIf: objectMemory wordSize > 4
>> +                       ifTrue: [((self isIntegerObject: self stackTop)
>> and: [rcvr = arg])
>> +                               ifTrue: ["Resolve case of ambiguity so as
>> to have comparison of exact values"
>> +                                       intArg := self integerValueOf:
>> self stackTop.
>> +                                       self pop: 2 thenPushBool: (rcvr
>> asInteger = intArg) not]
>> +                               ifFalse: [self pop: 2 thenPushBool: (rcvr
>> = arg) not]]
>> +                       ifFalse: [self pop: 2 thenPushBool: (rcvr = arg)
>> not]]!
>> -               [self pop: 2 thenPushBool: (rcvr = arg) not]!
>>
>> Item was changed:
>>   ----- Method: InterpreterProxy>>methodReturnString: (in category 'stack
>> access') -----
>>   methodReturnString: aCString
>> +       "Attempt to answer a ByteString for a given C string as the
>> result of a primitive."
>> -       "Sets the return value for a method."
>> -       "THIS IS DUBIOUS!!  CONSIDER REMOVING IT!!  RIGHT NOW IT IS NOT
>> SENT."
>>         <var: 'aCString' type: #'char *'>
>> +       aCString
>> +               ifNil: [primFailCode := PrimErrOperationFailed]
>> +               ifNotNil:
>> +                       [(self stringForCString: aCString)
>> +                               ifNil: [primFailCode := PrimErrNoMemory]
>> +                               ifNotNil: [:result| self pop:
>> argumentCount+1 thenPush: result]].
>> -       (self stringForCString: aCString)
>> -               ifNil: [primFailCode := PrimErrNoMemory]
>> -               ifNotNil: [:result| self pop: argumentCount+1 thenPush:
>> result].
>>         ^0!
>>
>> Item was changed:
>>   ----- Method: Spur64BitMemoryManager>>loadFloatOrIntFrom: (in category
>> 'interpreter access') -----
>>   loadFloatOrIntFrom: floatOrIntOop
>>         "If floatOrInt is an integer, then convert it to a C double float
>> and return it.
>>          If it is a Float, then load its value and return it.
>>          Otherwise fail -- ie return with primErrorCode non-zero."
>>
>>         <inline: true>
>>         <returnTypeC: #double>
>> +       | result tagBits |
>> -       | result tagBits shift |
>>         <var: #result type: #double>
>>
>>         (tagBits := floatOrIntOop bitAnd: self tagMask) ~= 0
>>                 ifTrue:
>>                         [tagBits = self smallFloatTag ifTrue:
>>                                 [^self smallFloatValueOf: floatOrIntOop].
>> +                        tagBits = self smallIntegerTag ifTrue:
>> -                        (tagBits = self smallIntegerTag
>> -                         and: [shift := 64 - self numTagBits - self
>> smallFloatMantissaBits.
>> -                               (self cCode: [floatOrIntOop << shift]
>> -                                               inSmalltalk:
>> [floatOrIntOop << shift bitAnd: 1 << 64 - 1]) >>> shift = floatOrIntOop])
>> ifTrue:
>>                                 [^(self integerValueOf: floatOrIntOop)
>> asFloat]]
>>                 ifFalse:
>>                         [(self classIndexOf: floatOrIntOop) =
>> ClassFloatCompactIndex ifTrue:
>>                                 [self cCode: '' inSmalltalk: [result :=
>> Float new: 2].
>>                                  self fetchFloatAt: floatOrIntOop + self
>> baseHeaderSize into: result.
>>                                  ^result]].
>>         coInterpreter primitiveFail.
>>         ^0.0!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>methodReturnString: (in category
>> 'plugin primitive support') -----
>>   methodReturnString: aCString
>> +       "Attempt to answer a ByteString for a given C string as the
>> result of a primitive."
>> -       "Sets the return value for a method."
>>         <var: 'aCString' type: #'char *'>
>> +       aCString
>> +               ifNil: [primFailCode := PrimErrOperationFailed]
>> +               ifNotNil:
>> +                       [(self stringForCString: aCString)
>> +                               ifNil: [primFailCode := PrimErrNoMemory]
>> +                               ifNotNil: [:result| self pop:
>> argumentCount+1 thenPush: result]].
>> -       self pop: argumentCount+1 thenPush: (objectMemory
>> stringForCString: aCString).
>>         ^0!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>primitiveFloatEqual:toArg: (in category
>> 'comparison float primitives') -----
>>   primitiveFloatEqual: rcvrOop toArg: argOop
>>         | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory loadFloatOrIntFrom: rcvrOop.
>>         arg := objectMemory loadFloatOrIntFrom: argOop.
>> +       self cppIf: objectMemory wordSize > 4
>> +               ifTrue: [rcvr = arg
>> +                       ifTrue:
>> +                               [(self isIntegerObject: argOop)
>> +                                       ifTrue:
>> +                                               ["Resolve case of
>> ambiguity so as to have comparison of exact values"
>> +                                               ^ rcvr asInteger = (self
>> integerValueOf: argOop)]
>> +                                       ifFalse: [(self isIntegerObject:
>> rcvrOop)
>> +                                               ifTrue:
>> +                                                       ["Same when used
>> from bytecodePrim...
>> +                                                       note that rcvr
>> and arg cannot be both integer (case is already handled)"
>> +                                                       ^ (self
>> integerValueOf: rcvrOop) = arg asInteger]]]].
>>         ^rcvr = arg!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>primitiveFloatGreater:thanArg: (in
>> category 'comparison float primitives') -----
>>   primitiveFloatGreater: rcvrOop thanArg: argOop
>>         | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory loadFloatOrIntFrom: rcvrOop.
>>         arg := objectMemory loadFloatOrIntFrom: argOop.
>> +       self cppIf: objectMemory wordSize > 4
>> +               ifTrue: [rcvr = arg
>> +                       ifTrue:
>> +                               [(self isIntegerObject: argOop)
>> +                                       ifTrue:
>> +                                               ["Resolve case of
>> ambiguity so as to have comparison of exact values"
>> +                                               ^ rcvr asInteger > (self
>> integerValueOf: argOop)]
>> +                                       ifFalse: [(self isIntegerObject:
>> rcvrOop)
>> +                                               ifTrue:
>> +                                                       ["Same when used
>> from bytecodePrim...
>> +                                                       note that rcvr
>> and arg cannot be both integer (case is already handled)"
>> +                                                       ^ (self
>> integerValueOf: rcvrOop) > arg asInteger]]]].
>>         ^rcvr > arg!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>primitiveFloatGreaterOrEqual:toArg: (in
>> category 'comparison float primitives') -----
>>   primitiveFloatGreaterOrEqual: rcvrOop toArg: argOop
>>         | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory loadFloatOrIntFrom: rcvrOop.
>>         arg := objectMemory loadFloatOrIntFrom: argOop.
>> +       self cppIf: objectMemory wordSize > 4
>> +               ifTrue: [rcvr = arg
>> +                       ifTrue:
>> +                               [(self isIntegerObject: argOop)
>> +                                       ifTrue:
>> +                                               ["Resolve case of
>> ambiguity so as to have comparison of exact values"
>> +                                               ^ rcvr asInteger >= (self
>> integerValueOf: argOop)]
>> +                                       ifFalse: [(self isIntegerObject:
>> rcvrOop)
>> +                                               ifTrue:
>> +                                                       ["Same when used
>> from bytecodePrim...
>> +                                                       note that rcvr
>> and arg cannot be both integer (case is already handled)"
>> +                                                       ^ (self
>> integerValueOf: rcvrOop) >= arg asInteger]]]].
>>         ^rcvr >= arg!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>primitiveFloatLess:thanArg: (in
>> category 'comparison float primitives') -----
>>   primitiveFloatLess: rcvrOop thanArg: argOop
>>         | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory loadFloatOrIntFrom: rcvrOop.
>>         arg := objectMemory loadFloatOrIntFrom: argOop.
>> +       self cppIf: objectMemory wordSize > 4
>> +               ifTrue: [rcvr = arg
>> +                       ifTrue:
>> +                               [(self isIntegerObject: argOop)
>> +                                       ifTrue:
>> +                                               ["Resolve case of
>> ambiguity so as to have comparison of exact values"
>> +                                               ^ rcvr asInteger < (self
>> integerValueOf: argOop)]
>> +                                       ifFalse: [(self isIntegerObject:
>> rcvrOop)
>> +                                               ifTrue:
>> +                                                       ["Same when used
>> from bytecodePrim...
>> +                                                       note that rcvr
>> and arg cannot be both integer (case is already handled)"
>> +                                                       ^ (self
>> integerValueOf: rcvrOop) < arg asInteger]]]].
>>         ^rcvr < arg!
>>
>> Item was changed:
>>   ----- Method: StackInterpreter>>primitiveFloatLessOrEqual:toArg: (in
>> category 'comparison float primitives') -----
>>   primitiveFloatLessOrEqual: rcvrOop toArg: argOop
>>         | rcvr arg |
>>         <var: #rcvr type: #double>
>>         <var: #arg type: #double>
>>
>>         rcvr := objectMemory loadFloatOrIntFrom: rcvrOop.
>>         arg := objectMemory loadFloatOrIntFrom: argOop.
>> +       self cppIf: objectMemory wordSize > 4
>> +               ifTrue: [rcvr = arg
>> +                       ifTrue:
>> +                               [(self isIntegerObject: argOop)
>> +                                       ifTrue:
>> +                                               ["Resolve case of
>> ambiguity so as to have comparison of exact values"
>> +                                               ^ rcvr asInteger <= (self
>> integerValueOf: argOop)]
>> +                                       ifFalse: [(self isIntegerObject:
>> rcvrOop)
>> +                                               ifTrue:
>> +                                                       ["Same when used
>> from bytecodePrim...
>> +                                                       note that rcvr
>> and arg cannot be both integer (case is already handled)"
>> +                                                       ^ (self
>> integerValueOf: rcvrOop) <= arg asInteger]]]].
>>         ^rcvr <= arg!
>>
>>
>
> --
> _,,,^..^,,,_
> best, Eliot
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20190827/ee7e3f4d/attachment-0001.html>


More information about the Vm-dev mailing list