[Haskell-cafe] Desired behaviour of rounding etc.

Simon Marlow marlowsd at gmail.com
Tue Oct 12 05:18:39 EDT 2010


On 09/10/2010 10:07, Daniel Fischer wrote:
> On Saturday 09 October 2010 06:34:32, Lennart Augustsson wrote:
>> That code is incorrect.  You can't assume that the base for floating
>> point numbers is 2, that's something you have to check.
>> (POWER6 and z9 has hardware support for base 10 floating point.)
>>
>>    -- Lennart
>
> Well, in light of
>
> -- We assume that FLT_RADIX is 2 so that we can use more efficient code
> #if FLT_RADIX != 2
> #error FLT_RADIX must be 2
> #endif
>      properFraction (F# x#)
>        = case decodeFloat_Int# x# of
>          (# m#, n# #) ->
>              let m = I# m#
>                  n = I# n#
>              in
>              if n>= 0
>              then (fromIntegral m * (2 ^ n), 0.0)
>
> appearing in the RealFrac instance for Float, I thought it would be a safe
> optimisation to use for Float and Double in GHC.Float (oddly, FLT_RADIX ==
> 2 is only used for Float, not for Double).
>
> I can of course wrap the base 2 code in an "#if FLT_RADIX == 2" and have
> general code for other bases, but as long as the #error stays, that seems
> superfluous.

Making the assumption is fine (as we do in the code above), but the 
important thing is to make the build fail in a very noisy way if the 
assumption turns out to be wrong (as above).

Cheers,
	Simon



>>
>> On Fri, Oct 8, 2010 at 2:08 PM, Daniel Fischer<daniel.is.fischer at web.de>
> wrote:
>>> The methods of the RealFrac class produce garbage when the value lies
>>> outside the range of the target type, e.g.
>>>
>>> Prelude GHC.Float>  truncate 1.234e11 :: Int  -- 32-bits
>>> -1154051584
>>>
>>> and, in the case of truncate, different garbage when the rewrite rule
>>> fires:
>>>
>>> Prelude GHC.Float>  double2Int 1.234e11
>>> -2147483648
>>>
>>> I'm currently working on faster implementations of properFraction,
>>> truncate, round, ceiling and floor for Float and Double, so I'd like
>>> to know
>>>
>>> - does it matter at all what garbage is returned in the above case?
>>> - if it does, what is the desired behaviour (at least for Int, I can't
>>> cater for all possibilities)?
>>>
>>>
>>> On a related note, in my benchmarks,
>>>
>>> truncFloatGen :: Integral a =>  Float ->  a
>>> truncFloatGen = fromInteger . truncFloatInteger
>>>
>>> truncFloatInteger :: Float ->  Integer
>>> truncFloatInteger x =
>>>   case decodeFloat x of
>>>     (m,e) | e == 0  ->  m
>>>           | e<  0   ->
>>>             let s = -e
>>>             in if m<  0
>>>                   then - ((-m) `shiftR` s)
>>>                   else m `shiftR` s
>>>           | otherwise ->  m `shiftL` e
>>>
>>> is more than twice as fast as GHC.Float.float2Int, the corresponding
>>> for Double almost twice as fast as double2Int.
>>>
>>> Can anybody confirm that the above is faster than float2Int on other
>>> machines/architectures?
>>>
>>> Cheers,
>>> Daniel
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries



More information about the Libraries mailing list