[Haskell-cafe] Re: A question about "monad laws"
Ben Franksen
ben.franksen at online.de
Thu Feb 14 13:32:55 EST 2008
Wilhelm B. Kloke wrote:
> ajb at spamcop.net <ajb at spamcop.net> schrieb:
>> G'day all.
>>
>> Richard A. O'Keefe wrote:
>>
>>> Hmm. Personally, I've never seen an algorithm where comparing for exact
>>> equality was algorithmically necessary.
>>
>> One trick I've occasionally used is to avoid the need for a discriminated
>> union of floating point and integer types by just using a floating point
>> number.
>
> IMHO it is a perfectly good idea to use the FP processor for integer
> computations. You can use the Inexact Trap as Overflow Exception,
> a service you don't get from i386 (and most other) hardware for int
> operations. Of course your integers are limited to 24bit+sign in
> single precision and 54bit+sign in double. In i387 extended precision
> you get 64bit+sign.
>
> I would consider a good idea if ghc would provide language support to
> this sort of integers.
No need, you can do that for yourself:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype DInt = DInt Double deriving (Eq, Ord, Enum, Num)
instance Show DInt where show (DInt x) = show (truncate x :: Integer)
You can even make it H98 by defining the instances manually...
Cheers
Ben
More information about the Haskell-Cafe
mailing list