Re: [Haskell-cafe] 1/0

2008-06-16 Thread Henning Thielemann


On Mon, 16 Jun 2008, Dan Doel wrote:


On Monday 16 June 2008, Evan Laforge wrote:


(huge negative number)

Ok, so integral types don't have that exceptional value.  Shouldn't
trying to convert NaN or Infinity to an Integral throw something?  Is
it a performance thing?  I'd think if you're converting to Integer you
don't really need hardware level performance anyway, so a couple of
checks wouldn't kill anyone.


This is a (known by some) bug of sorts in the various floating point ->
integral transformations (which ultimately boil down to decodeFloat or
something like that at some point). It apparently doesn't know about the
various exceptional values in the IEEE representation, so it just treats the
representation like any other value. Infinity and NaN look like various huge
numbers if you interpret them like any other value, so that's what you get
out of round/ceiling/floor/etc.

It's not ideal, but I guess no one's bothered to fix it. Might be something to
bring up on the libraries mailing list.


This could be combined with improving performance:
   http://hackage.haskell.org/trac/ghc/ticket/2281
   http://hackage.haskell.org/trac/ghc/ticket/2271
   http://hackage.haskell.org/trac/ghc/ticket/1434
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Richard A. O'Keefe

Since Haskell-Café often strays into mathematics,
this may not be too far off topic.

On 17 Jun 2008, at 2:29 pm, Evan Laforge wrote:

Yeah, on reflection, I think my "intuition" derives from me asking a
math teacher back in high school "isn't n/0 infinity?" after looking
at a graph, to which he said "no, it's undefined, you can only say it
approaches infinity in the limit, but it isn't infinity".


Let's put this kindly:  it is POSSIBLE that your maths teacher knew
what he was talking about and was just telling what the "Science of
Discworld" authors call "lies-to-children".  It is certainly likely
that it didn't occur to him that you might transfer what he said
about the mathematical real numbers to a rather different algebraic
system, IEEE floats.

The usual "real numbers" R form an ordered field.
*In that structure*, n/0 is undefined.
But there is another algebraic structure which includes all
the real numbers plus one more: infinity.
It's call the real projective line.
See http://en.wikipedia.org/wiki/Real_projective_line
In that structure, n/0 is perfectly well defined, and is indeed
infinity.  That structure has all the properties you really need
to do calculus, but isn't a field and isn't ordered.  However,
whenever an operation on elements of R is defined, the
analogous operation on the corresponding elements of \hat R is
defined and has the corresponding value.

Basically, you can define operations any way you want as long as
you are willing to live with the consequences.  For example, it
turns out to be possible to define an alternative arithmetic in
which (-x)*(-y) = -(x*y) for positive x, y.  The price is that
it doesn't satisfy all the usual axioms, though it does satisfy
other possibly useful ones that the usual systems don't.

In an analogous way, the IEEE designers decided that it would be
useful to have +/- epsilon instead of 0 and +/- (1/epsilon)
instead of infinity, but then decided that the ordering operations
should identify -epsilon with +epsilon, so the result still isn't
quite a proper total order, even ignoring NaNs.  (What happens if
you sort a list of mixed +0.0 and -0.0?  What, if anything,
_should_ happen?)  They obtained the benefits they wanted, at the
price of making the resulting structure less like R.  But then,
floating point numbers never were _very_ much like R to start with.
It's not clear to me that *R offers anything more than a heuristic
analogy to IEEE arithmetic.  For one thing, *R is ordered.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Evan Laforge
>> ... so I see from the archives that Infinity is mandated by ieee754
>> even though my intuition says both should be NaN.
>
> Other people have other intuitions.  It may be that your intuition
> is telling you that neither result should be an ordinary number,
> and if that's what it's really telling you, it's right: the C
> function isfinite(x) is true of all signed zero, subnormal, or
> normal x, false of signed infinities and NaNs.

Yeah, on reflection, I think my "intuition" derives from me asking a
math teacher back in high school "isn't n/0 infinity?" after looking
at a graph, to which he said "no, it's undefined, you can only say it
approaches infinity in the limit, but it isn't infinity".

>> Every other language throws an exception, even C will crash the
>>
>> program,
>
> Not true.  C99 *definitely* allows both infinities and NaNs (see
> Annex F of the C99 standard) and C89 practice also allowed it.
> Some C89 systems required you to use signal() with SIGFPE to
> turn IEEE extended results into exceptions; others required you
> to use signal() to disable this; others used yet other means.

Yes, I was mistaken here, as has been pointed out.

And I should definitely know better than to make some generalization
about "every other language" among this crowd :)

> (Of course, in C what you typically get is garbage, but that can
> be put more generally...)

Heh, one for the C-bashing quotes file...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Richard A. O'Keefe


On 17 Jun 2008, at 11:07 am, Evan Laforge wrote:


So, I know this has been discussed before, but:


1/0

Infinity

0/0

NaN

... so I see from the archives that Infinity is mandated by ieee754
even though my intuition says both should be NaN.


Other people have other intuitions.  It may be that your intuition
is telling you that neither result should be an ordinary number,
and if that's what it's really telling you, it's right: the C
function isfinite(x) is true of all signed zero, subnormal, or
normal x, false of signed infinities and NaNs.

> Every other language throws an exception, even C will crash the

program,


Not true.  C99 *definitely* allows both infinities and NaNs (see
Annex F of the C99 standard) and C89 practice also allowed it.
Some C89 systems required you to use signal() with SIGFPE to
turn IEEE extended results into exceptions; others required you
to use signal() to disable this; others used yet other means.

The Scheme systems I tried turn (/ 1.0 0.0) into a printed
representation of IEEE infinity.  Of the Prolog systems I checked,
some did and some didn't.  The Standard ML system I tried gave
"inf" as the response to 1.0/0.0.

Basically, with any programming language implementation that
truthfully claims conformance to IEEE 754 or a successor standard,
x/0 MUST NOT crash unless your program explicitly asks for such
behaviour.  As for programming language implementations that do
not make such a claim, who knows what they will do?

Since integers do not have the special IEEE values, conversion
of IEEE values to integral values really ought to be checked.
(Of course, in C what you typically get is garbage, but that can
be put more generally...)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Brandon S. Allbery KF8NH


On 2008 Jun 16, at 19:18, David Roundy wrote:

On Mon, Jun 16, 2008 at 4:07 PM, Evan Laforge <[EMAIL PROTECTED]>  
wrote:

Every other language throws an exception, even C will crash the
program, so I'm guessing it's telling the processor / OS to turn  
these

into signals, while GHC is turning that off.  Or something.  But then
what about this note in Control.Exception:


That's just not true.  It depends on how your system (compiler?) is
configured, but the default on most systems that I've used is to
return NaNs.



It's how the system FPU is configured; most FPU hardware on Unixlike  
systems let you configure the FPU behavior on a per-process basis,  
although the amount of configurability may vary.


That said, the divide by zero exception you get in both C and Haskell  
is *integer* divide-by-zero.  Floating is mandated by IEEE standard to  
produce Inf (but as said above, can usually be configured).


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread David Roundy
On Mon, Jun 16, 2008 at 05:39:39PM -0700, Don Stewart wrote:
> > decodeFloat really ought to be a partial function, and this should
> > be a crashing bug, if the standard libraries were better-written.
> 
> It's a bug in the H98 report then:
> 
> Section 6.4.6:
> 
> "The function decodeFloat applied to a real floating-point number returns
> the significand expressed as an Integer and an appropriately scaled
> exponent (an Int). If decodeFloat x yields (m,n), then x is equal in value
> to mb^n, where b is the floating-point radix, and furthermore, either m
> and n are both zero or else b^d-1<=m floatDigits x.  encodeFloat performs the inverse of this transformation.
> "

Yes, it is a bug in the report, that it doesn't fully specify the
behavior this function when given a NaN or infinity.  There's also a
bug in the standard libraries, which is that they don't conform to the
report.

let x = 0/0
let (m,n) = decodeFloat x
Prelude> (m,n)
(-6755399441055744,972)
Prelude> let x = 0/0
Prelude> x
NaN
Prelude> let d = floatDigits x
Prelude> let (m,n) = decodeFloat x
Prelude> let x' = (fromInteger m :: Double)*2^n
Prelude> x'
-Infinity
Prelude> 2^d-1<=m
False
Prelude> m<2^d
True

So for the ghc decodeFloat, when operating on a NaN, the
specifications of decodeFloat are almost completely unsatisfied.  On
the plus side, at least it's true that mhttp://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread John Meacham
On Mon, Jun 16, 2008 at 05:39:39PM -0700, Don Stewart wrote:
> It's a bug in the H98 report then:

Yes, I consider a whole lot of the floating point stuff in the report a
bug of sorts IMHO :) It is certainly something that I hope to work on for
Haskell'. 

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Don Stewart
droundy:
> On Mon, Jun 16, 2008 at 05:08:36PM -0700, Don Stewart wrote:
> > droundy:
> > > On Mon, Jun 16, 2008 at 04:50:05PM -0700, John Meacham wrote:
> > > > On Mon, Jun 16, 2008 at 04:41:23PM -0700, Evan Laforge wrote:
> > > > > But what about that NaN->Integer conversion thing?
> > > > 
> > > > I think that may be a bug or at least a misfeature. The standard is
> > > > somewhat vauge on a lot of issues dealing with floating point since
> > > > it is such a tricky subject and depends a lot on the environment. The
> > > > various rounding funcitons are particularly ugly IMHO. I added varients
> > > > of them that preserved the floating point type and properly implemented
> > > > IEEE behavior for jhc.
> > > 
> > > I think the Data.Binary guys think it's a feature, since they rely in
> > > this behavior (well, they rely on the equivalently-foolish behavior of
> > > toRational).  I think it's a bug.
> > 
> > You mean:
> > 
> > instance Binary Double where
> > put d = put (decodeFloat d)
> > get   = liftM2 encodeFloat get get
> > 
> > ?
> > 
> > if you've a portable Double decoding that works in GHC and Hugs, I'm
> > accepting patches.
> 
> I really don't understand why being portable is such an issue.  Is it
> really better to behave wrong on every platform rather than behaving
> wrong on a very small minority of platforms?

The Binary instances are required to be portable, as that's the part
of the definition of Binary's mandate: a portable binary encoding.
  
> Anyhow, I've not hacked on binary, because I've not used it, and have
> trouble seeing when I would use it.  So maybe I shouldn't have brought
> the subject up, except that this use of decodeFloat/encodeFloat is a
> particularly egregious misuse of floating point numbers.  

> decodeFloat
> really ought to be a partial function, and this should be a crashing
> bug, if the standard libraries were better-written.

It's a bug in the H98 report then:

Section 6.4.6:

"The function decodeFloat applied to a real floating-point number returns
the significand expressed as an Integer and an appropriately scaled
exponent (an Int). If decodeFloat x yields (m,n), then x is equal in value
to mb^n, where b is the floating-point radix, and furthermore, either m
and n are both zero or else b^d-1<=mhttp://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread David Roundy
On Mon, Jun 16, 2008 at 05:08:36PM -0700, Don Stewart wrote:
> droundy:
> > On Mon, Jun 16, 2008 at 04:50:05PM -0700, John Meacham wrote:
> > > On Mon, Jun 16, 2008 at 04:41:23PM -0700, Evan Laforge wrote:
> > > > But what about that NaN->Integer conversion thing?
> > > 
> > > I think that may be a bug or at least a misfeature. The standard is
> > > somewhat vauge on a lot of issues dealing with floating point since
> > > it is such a tricky subject and depends a lot on the environment. The
> > > various rounding funcitons are particularly ugly IMHO. I added varients
> > > of them that preserved the floating point type and properly implemented
> > > IEEE behavior for jhc.
> > 
> > I think the Data.Binary guys think it's a feature, since they rely in
> > this behavior (well, they rely on the equivalently-foolish behavior of
> > toRational).  I think it's a bug.
> 
> You mean:
> 
> instance Binary Double where
> put d = put (decodeFloat d)
> get   = liftM2 encodeFloat get get
> 
> ?
> 
> if you've a portable Double decoding that works in GHC and Hugs, I'm
> accepting patches.

I really don't understand why being portable is such an issue.  Is it
really better to behave wrong on every platform rather than behaving
wrong on a very small minority of platforms?

Anyhow, I've not hacked on binary, because I've not used it, and have
trouble seeing when I would use it.  So maybe I shouldn't have brought
the subject up, except that this use of decodeFloat/encodeFloat is a
particularly egregious misuse of floating point numbers.  decodeFloat
really ought to be a partial function, and this should be a crashing
bug, if the standard libraries were better-written.

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Don Stewart
droundy:
> On Mon, Jun 16, 2008 at 04:50:05PM -0700, John Meacham wrote:
> > On Mon, Jun 16, 2008 at 04:41:23PM -0700, Evan Laforge wrote:
> > > But what about that NaN->Integer conversion thing?
> > 
> > I think that may be a bug or at least a misfeature. The standard is
> > somewhat vauge on a lot of issues dealing with floating point since
> > it is such a tricky subject and depends a lot on the environment. The
> > various rounding funcitons are particularly ugly IMHO. I added varients
> > of them that preserved the floating point type and properly implemented
> > IEEE behavior for jhc.
> 
> I think the Data.Binary guys think it's a feature, since they rely in
> this behavior (well, they rely on the equivalently-foolish behavior of
> toRational).  I think it's a bug.

You mean:

instance Binary Double where
put d = put (decodeFloat d)
get   = liftM2 encodeFloat get get

?

if you've a portable Double decoding that works in GHC and Hugs, I'm
accepting patches.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread David Roundy
On Mon, Jun 16, 2008 at 04:50:05PM -0700, John Meacham wrote:
> On Mon, Jun 16, 2008 at 04:41:23PM -0700, Evan Laforge wrote:
> > But what about that NaN->Integer conversion thing?
> 
> I think that may be a bug or at least a misfeature. The standard is
> somewhat vauge on a lot of issues dealing with floating point since
> it is such a tricky subject and depends a lot on the environment. The
> various rounding funcitons are particularly ugly IMHO. I added varients
> of them that preserved the floating point type and properly implemented
> IEEE behavior for jhc.

I think the Data.Binary guys think it's a feature, since they rely in
this behavior (well, they rely on the equivalently-foolish behavior of
toRational).  I think it's a bug.

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread John Meacham
On Mon, Jun 16, 2008 at 04:41:23PM -0700, Evan Laforge wrote:
> But what about that NaN->Integer conversion thing?

I think that may be a bug or at least a misfeature. The standard is
somewhat vauge on a lot of issues dealing with floating point since
it is such a tricky subject and depends a lot on the environment. The
various rounding funcitons are particularly ugly IMHO. I added varients
of them that preserved the floating point type and properly implemented
IEEE behavior for jhc.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Dan Doel
On Monday 16 June 2008, Evan Laforge wrote:
> So, I know this has been discussed before, but:
> > 1/0
>
> Infinity
>
> > 0/0
>
> NaN
>
> ... so I see from the archives that Infinity is mandated by ieee754
> even though my intuition says both should be NaN.
>
> Every other language throws an exception, even C will crash the
> program, so I'm guessing it's telling the processor / OS to turn these
> into signals, while GHC is turning that off.  Or something.  But then
> what about this note in Control.Exception:

#include 
#include 

int main (int argc, char **argv)
{
  float f1 = 1.0/0.0;
  float f2 = 0.0/0.0;

  printf("%f\n%f\n", f1, f2);

  return EXIT_SUCCESS;
}

% ./Inf
inf
nan

In a Haskell program, 1/0 is floating point division. In C, 1/0 is integer 
division, which may get implicitly converted to a floating point if you 
say "float f = 1/0;". That's why you get the exception in C.

> but how about this:
> > round (0/0) :: Integer
>
> (huge negative number)
>
> Ok, so integral types don't have that exceptional value.  Shouldn't
> trying to convert NaN or Infinity to an Integral throw something?  Is
> it a performance thing?  I'd think if you're converting to Integer you
> don't really need hardware level performance anyway, so a couple of
> checks wouldn't kill anyone.

This is a (known by some) bug of sorts in the various floating point -> 
integral transformations (which ultimately boil down to decodeFloat or 
something like that at some point). It apparently doesn't know about the 
various exceptional values in the IEEE representation, so it just treats the 
representation like any other value. Infinity and NaN look like various huge 
numbers if you interpret them like any other value, so that's what you get 
out of round/ceiling/floor/etc.

It's not ideal, but I guess no one's bothered to fix it. Might be something to 
bring up on the libraries mailing list.

-- Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Evan Laforge
> No, The issue is that '/' is always floating point division in haskell,
> for integer division, use `div`.
>
> 1 `div` 0 throws an exception like you expect.
>
> GHC behaves exactly the same as C here. But in C whether '/' means
> floating point or integral division depends on the types of its
> arguments, in haskell they are separate operators.

Aha, I was missing something.  Indeed, 1.0/0.0 gives me infinity with
C.  Thanks for the clarification.  Python does throw for 1.0/0.0, but
I think there's a (not very commonly used) module to turn that off.
It might be nice for GHC to have a some way to turn exceptions on, but
I can accept getting NaNs, and doing the ieee754 thing by default
seems entirely reasonable.


But what about that NaN->Integer conversion thing?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread Xiao-Yong Jin
"Evan Laforge" <[EMAIL PROTECTED]> writes:

> So, I know this has been discussed before, but:
>
>> 1/0
> Infinity
>> 0/0
> NaN
>
> ... so I see from the archives that Infinity is mandated by ieee754
> even though my intuition says both should be NaN.
>
> Every other language throws an exception, even C will crash the
> program, so I'm guessing it's telling the processor / OS to turn these
> into signals, while GHC is turning that off. [...]

No, C will not, with floating point type.  The following
program prints out a string "inf\n".

#include 
int main (void) 
{ 
double a=1, b=0; 
double i; 
i = a / b; 
printf ("%g\n",i);
return 0;
}

I believe Haskell is behaving rationally.

Cheers,
Xiao-Yong
-- 
c/*__o/*
<\ * (__
*/\  <
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread John Meacham
On Mon, Jun 16, 2008 at 04:07:33PM -0700, Evan Laforge wrote:
> So, I know this has been discussed before, but:
> Every other language throws an exception, even C will crash the
> program, so I'm guessing it's telling the processor / OS to turn these
> into signals, while GHC is turning that off.  Or something.  But then
> what about this note in Control.Exception:

No, The issue is that '/' is always floating point division in haskell,
for integer division, use `div`.

1 `div` 0 throws an exception like you expect. 

GHC behaves exactly the same as C here. But in C whether '/' means
floating point or integral division depends on the types of its
arguments, in haskell they are separate operators.

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread David Roundy
On Mon, Jun 16, 2008 at 4:18 PM, David Roundy <[EMAIL PROTECTED]> wrote:
> On Mon, Jun 16, 2008 at 4:07 PM, Evan Laforge <[EMAIL PROTECTED]> wrote:
>> Every other language throws an exception, even C will crash the
>> program, so I'm guessing it's telling the processor / OS to turn these
>> into signals, while GHC is turning that off.  Or something.  But then
>> what about this note in Control.Exception:
>
> That's just not true.  It depends on how your system (compiler?) is
> configured, but the default on most systems that I've used is to
> return NaNs.

Sorry, I just read my post, and realized I quoted too much.  I was
responding to the first sentence about other languages, thinking of
octave, C and C++.

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 1/0

2008-06-16 Thread David Roundy
On Mon, Jun 16, 2008 at 4:07 PM, Evan Laforge <[EMAIL PROTECTED]> wrote:
> So, I know this has been discussed before, but:
>
>> 1/0
> Infinity
>> 0/0
> NaN
>
> ... so I see from the archives that Infinity is mandated by ieee754
> even though my intuition says both should be NaN.

There is a good reason for 1/0 being infinity, as it allows correct
programs to give correct answers even in the presence of underflow and
overflow.

> Every other language throws an exception, even C will crash the
> program, so I'm guessing it's telling the processor / OS to turn these
> into signals, while GHC is turning that off.  Or something.  But then
> what about this note in Control.Exception:

That's just not true.  It depends on how your system (compiler?) is
configured, but the default on most systems that I've used is to
return NaNs.

David
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe