Potential issue of primitiveTimesTwoPower in Spur 64

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

Potential issue of primitiveTimesTwoPower in Spur 64

Nicolas Cellier
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.
Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Nicolas Cellier
 


2015-02-11 23:57 GMT+01:00 Nicolas Cellier <[hidden email]>:
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.

of course, it's the same for primitiveSmallFloatTimesTwoPower (where things will really happen most of the time in Spur64)

Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Nicolas Cellier
 


2015-02-12 0:00 GMT+01:00 Nicolas Cellier <[hidden email]>:


2015-02-11 23:57 GMT+01:00 Nicolas Cellier <[hidden email]>:
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...

ah ah, but these do not even work in 32 bits COG currently:

Float infinity timesTwoPower: -16r10000000001.
0.0 timesTwoPower: 16r10000000001.

Both answer NaN but shouldn't...
The image side fallback code needs more care...

 
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.

of course, it's the same for primitiveSmallFloatTimesTwoPower (where things will really happen most of the time in Spur64)


Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Eliot Miranda-2
In reply to this post by Nicolas Cellier
 
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Eliot Miranda-2
 
and of course I meant

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
 twiceMaxExponent := 2 * (1 << self floatExponentBits).
 arg < twiceMaxExponent negated ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

On Wed, Feb 11, 2015 at 5:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot



--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Eliot Miranda-2
 
Hmm, close, but I need to check explicitly for zero.  Here's the version for the FloatMathPlugin (& with more conventional formatting :-) ):

primitiveTimesTwoPower
"Computes E raised to the receiver power."
| rcvr arg twiceMaxExponent result |
<export: true>
<var: #rcvr type: #double>
<var: #result type: #double>
arg := interpreterProxy stackIntegerValue: 0.
rcvr := interpreterProxy stackFloatValue: 1.
(interpreterProxy failed) ifTrue:
[^nil].
((self isFinite: rcvr) and: [rcvr ~= 0.0])
ifFalse:
[result := rcvr]
ifTrue:
[twiceMaxExponent := 2 * (1 << 11).
arg < twiceMaxExponent negated
ifTrue:
[result := 0.0]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := 1.0e200 / 1.0e-200]
ifFalse:
[result := self cCode: '__ieee754_ldexp(rcvr, arg)'
inSmalltalk: [rcvr timesTwoPower: arg]]]].
(self isnan: result) ifTrue:
[^interpreterProxy primitiveFail].
interpreterProxy
pop: interpreterProxy methodArgumentCount + 1;
pushFloat: result

On Wed, Feb 11, 2015 at 5:43 PM, Eliot Miranda <[hidden email]> wrote:
and of course I meant

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
 twiceMaxExponent := 2 * (1 << self floatExponentBits).
 arg < twiceMaxExponent negated ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

On Wed, Feb 11, 2015 at 5:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot



--
best,
Eliot



--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Eliot Miranda-2
 
Again not close enough.  If value < 0, then result is < 0, so

primitiveTimesTwoPower
<option: #Spur64BitMemoryManager>
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
((self isFinite: rcvr) and: [rcvr ~= 0])
ifFalse:
[result := rcvr]
ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent negated
ifTrue:
[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := rcvr < 0.0 ifTrue: [-1.0e200 / 10.e-200] ifFalse: 1.0e200 / 1.0e-200]]
ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

Right?

On Wed, Feb 11, 2015 at 5:57 PM, Eliot Miranda <[hidden email]> wrote:
Hmm, close, but I need to check explicitly for zero.  Here's the version for the FloatMathPlugin (& with more conventional formatting :-) ):

primitiveTimesTwoPower
"Computes E raised to the receiver power."
| rcvr arg twiceMaxExponent result |
<export: true>
<var: #rcvr type: #double>
<var: #result type: #double>
arg := interpreterProxy stackIntegerValue: 0.
rcvr := interpreterProxy stackFloatValue: 1.
(interpreterProxy failed) ifTrue:
[^nil].
((self isFinite: rcvr) and: [rcvr ~= 0.0])
ifFalse:
[result := rcvr]
ifTrue:
[twiceMaxExponent := 2 * (1 << 11).
arg < twiceMaxExponent negated
ifTrue:
[result := 0.0]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := 1.0e200 / 1.0e-200]
ifFalse:
[result := self cCode: '__ieee754_ldexp(rcvr, arg)'
inSmalltalk: [rcvr timesTwoPower: arg]]]].
(self isnan: result) ifTrue:
[^interpreterProxy primitiveFail].
interpreterProxy
pop: interpreterProxy methodArgumentCount + 1;
pushFloat: result

On Wed, Feb 11, 2015 at 5:43 PM, Eliot Miranda <[hidden email]> wrote:
and of course I meant

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
 twiceMaxExponent := 2 * (1 << self floatExponentBits).
 arg < twiceMaxExponent negated ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

On Wed, Feb 11, 2015 at 5:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot



--
best,
Eliot



--
best,
Eliot



--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Nicolas Cellier
 


2015-02-12 3:02 GMT+01:00 Eliot Miranda <[hidden email]>:
 
Again not close enough.  If value < 0, then result is < 0, so

primitiveTimesTwoPower
<option: #Spur64BitMemoryManager>
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
((self isFinite: rcvr) and: [rcvr ~= 0])
ifFalse:
[result := rcvr]
ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent negated
ifTrue:
[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := rcvr < 0.0 ifTrue: [-1.0e200 / 10.e-200] ifFalse: 1.0e200 / 1.0e-200]]
ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

Right?

I was focused on image side fallback code and came up to more or less the same
So it sounds very good to me :)

We still have a compiler warning for long -> int,.
For sure, we can ignore it this time...
But this kind of false warning is pesky.
The risk is to drown a true positive into a flow of false ones...

Using an argument > 2^31 is more theoretical than practicle. It should be very rare.
So once we have image side for handling this rare case, I wonder if it is really necessary to complexify the primitive...
And it's good anyway to have a fallback code, it makes the primitives optional and lower the barrier for guys doing experiments like Bert.
So I would say let the primitive fail, and eliminate the warning.



On Wed, Feb 11, 2015 at 5:57 PM, Eliot Miranda <[hidden email]> wrote:
Hmm, close, but I need to check explicitly for zero.  Here's the version for the FloatMathPlugin (& with more conventional formatting :-) ):

primitiveTimesTwoPower
"Computes E raised to the receiver power."
| rcvr arg twiceMaxExponent result |
<export: true>
<var: #rcvr type: #double>
<var: #result type: #double>
arg := interpreterProxy stackIntegerValue: 0.
rcvr := interpreterProxy stackFloatValue: 1.
(interpreterProxy failed) ifTrue:
[^nil].
((self isFinite: rcvr) and: [rcvr ~= 0.0])
ifFalse:
[result := rcvr]
ifTrue:
[twiceMaxExponent := 2 * (1 << 11).
arg < twiceMaxExponent negated
ifTrue:
[result := 0.0]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := 1.0e200 / 1.0e-200]
ifFalse:
[result := self cCode: '__ieee754_ldexp(rcvr, arg)'
inSmalltalk: [rcvr timesTwoPower: arg]]]].
(self isnan: result) ifTrue:
[^interpreterProxy primitiveFail].
interpreterProxy
pop: interpreterProxy methodArgumentCount + 1;
pushFloat: result

On Wed, Feb 11, 2015 at 5:43 PM, Eliot Miranda <[hidden email]> wrote:
and of course I meant

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
 twiceMaxExponent := 2 * (1 << self floatExponentBits).
 arg < twiceMaxExponent negated ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

On Wed, Feb 11, 2015 at 5:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot



--
best,
Eliot



--
best,
Eliot



--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: Potential issue of primitiveTimesTwoPower in Spur 64

Eliot Miranda-2
 


On Wed, Feb 11, 2015 at 6:27 PM, Nicolas Cellier <[hidden email]> wrote:
 


2015-02-12 3:02 GMT+01:00 Eliot Miranda <[hidden email]>:
 
Again not close enough.  If value < 0, then result is < 0, so

primitiveTimesTwoPower
<option: #Spur64BitMemoryManager>
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
((self isFinite: rcvr) and: [rcvr ~= 0])
ifFalse:
[result := rcvr]
ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent negated
ifTrue:
[result := rcvr < 0.0 ifTrue: [-0.0] ifFalse: [0.0]]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := rcvr < 0.0 ifTrue: [-1.0e200 / 10.e-200] ifFalse: 1.0e200 / 1.0e-200]]
ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

Right?

I was focused on image side fallback code and came up to more or less the same
So it sounds very good to me :)

We still have a compiler warning for long -> int,.
For sure, we can ignore it this time...
But this kind of false warning is pesky.
The risk is to drown a true positive into a flow of false ones...

Using an argument > 2^31 is more theoretical than practicle. It should be very rare.
So once we have image side for handling this rare case, I wonder if it is really necessary to complexify the primitive...
And it's good anyway to have a fallback code, it makes the primitives optional and lower the barrier for guys doing experiments like Bert.
So I would say let the primitive fail, and eliminate the warning.

I was thinking the same thing.  So something like

     (objectMemory bytesPerOop > 4
      and: [arg > (1 << 30) or: [arg < (-1 << 30)]]) ifTrue:
        [^self primtiiveFail]

and then cast the arg to (int) to avoid the warning.  I'll make it so tomorrow.
 



On Wed, Feb 11, 2015 at 5:57 PM, Eliot Miranda <[hidden email]> wrote:
Hmm, close, but I need to check explicitly for zero.  Here's the version for the FloatMathPlugin (& with more conventional formatting :-) ):

primitiveTimesTwoPower
"Computes E raised to the receiver power."
| rcvr arg twiceMaxExponent result |
<export: true>
<var: #rcvr type: #double>
<var: #result type: #double>
arg := interpreterProxy stackIntegerValue: 0.
rcvr := interpreterProxy stackFloatValue: 1.
(interpreterProxy failed) ifTrue:
[^nil].
((self isFinite: rcvr) and: [rcvr ~= 0.0])
ifFalse:
[result := rcvr]
ifTrue:
[twiceMaxExponent := 2 * (1 << 11).
arg < twiceMaxExponent negated
ifTrue:
[result := 0.0]
ifFalse:
[arg > twiceMaxExponent
ifTrue:
[result := 1.0e200 / 1.0e-200]
ifFalse:
[result := self cCode: '__ieee754_ldexp(rcvr, arg)'
inSmalltalk: [rcvr timesTwoPower: arg]]]].
(self isnan: result) ifTrue:
[^interpreterProxy primitiveFail].
interpreterProxy
pop: interpreterProxy methodArgumentCount + 1;
pushFloat: result

On Wed, Feb 11, 2015 at 5:43 PM, Eliot Miranda <[hidden email]> wrote:
and of course I meant

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
 twiceMaxExponent := 2 * (1 << self floatExponentBits).
 arg < twiceMaxExponent negated ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result

On Wed, Feb 11, 2015 at 5:41 PM, Eliot Miranda <[hidden email]> wrote:
Hi Nicolas,

On Wed, Feb 11, 2015 at 2:57 PM, Nicolas Cellier <[hidden email]> wrote:
 
Some C functions in libm only take an int, not a long.
In 32 bits int=long, so no problem.
In 64 bits generally int=32 bits, long=64 bits, so casting a long to int might lead to catastrophic loss and unexpected behavior.

This is the case for example in primitiveTimesTwoPower
    | rcvr arg |
    <var: #rcvr type: #double>
    arg := self popInteger.
    rcvr := self popFloat.
    self successful
        ifTrue: [ self pushFloat: (self cCode: 'ldexp(rcvr, arg)' inSmalltalk: [rcvr timesTwoPower: arg]) ]
        ifFalse: [ self unPop: 2 ]

arg will be a long in Spur64, won't it?
but ldexp only takes an int
    double ldexp(double x, int exp);.

So guess what if we call (1.0 timesTwoPower: 16r10000000001)...
Normally there should be a C compiler warning, and we should care of it.

To solve this, maybe we need a
   
    <var: #arg type: #int>
    arg := self signed32BitValueOf: stackTop.


I think we can check intelligently.  We know that for a finite non-zero value,  ldexp(value, n) is infinite if n > (2 * max exponent) and zero if n < (2 * max exponent), that for a NaN value, ldexp(value, n) is NaN and for an infinite value ldexp(value,n) is infinite, and for a 0 value, it is zero.  So I propose

primitiveTimesTwoPower
| rcvr result arg twiceMaxExponent |
<var: #rcvr type: #double>
<var: #result type: #double>
arg := self stackTop.
(objectMemory isIntegerObject: arg) ifFalse:
[^self primitiveFailFor: PrimErrBadArgument].
rcvr := objectMemory floatValueOf: (self stackValue: 1).
(self isFinite: rcvr) ifFalse:
[result := rcvr] ifTrue:
[arg := objectMemory integerValueOf: arg.
twiceMaxExponent := 2 * (1 << self floatExponentBits).
arg < twiceMaxExponent ifTrue:
[result := 0.0] ifFalse:
[arg > twiceMaxExponent ifTrue:
[result := 1.0e200 / 1.0e-200] ifFalse:
[result := self cCode: [self ld: rcvr exp: arg]
inSmalltalk: [rcvr timesTwoPower: arg]]]].
self pop: 2 thenPushFloat: result
--
best,
Eliot



--
best,
Eliot



--
best,
Eliot



--
best,
Eliot






--
best,
Eliot