#4344: Better toRational for Float and Double
----------------------------------------+-----------------------------------
    Reporter:  daniel.is.fischer        |        Owner:                         
        Type:  bug                      |       Status:  new                    
    Priority:  normal                   |    Milestone:                         
   Component:  Compiler                 |      Version:  6.12.3                 
    Keywords:  toRational, performance  |     Testcase:                         
   Blockedby:                           |   Difficulty:                         
          Os:  Unknown/Multiple         |     Blocking:                         
Architecture:  Unknown/Multiple         |      Failure:  Runtime performance bug
----------------------------------------+-----------------------------------

Comment(by daniel.is.fischer):

 Very nice. The simpler code is indeed faster. With
 {{{
 floatRat :: Float -> Rational
 floatRat x
     | x == 0    = 0 :% 1
     | otherwise =
       case decodeFloat x of
         (m, e) | e >= 0 -> (m `shiftL` e) :% 1
                | otherwise ->
                  case fromInteger m :: Int of
                     m' | m' .&. 1 == 0 ->
                             shiftOutZeros m' (-e)
                        | otherwise -> m :% (1 `shiftL` (-e))

 doubRat :: Double -> Rational
 doubRat x
     | x == 0    = 0 :% 1
     | otherwise =
       case decodeFloat x of
         (m,e) | e >= 0 -> (m `shiftL` e) :% 1
               | otherwise -> shiftOutZeros (fromInteger m :: Int64) (-e)

 {-# SPECIALISE shiftOutZeros :: Int -> Int -> Rational,
                                 Int64 -> Int -> Rational #-}
 -- Precondition: first arg nonzero, second arg > 0
 -- To be called only from 'toRational'
 shiftOutZeros :: (Integral a, Bits a) => a -> Int -> Rational
 shiftOutZeros m e
     | e <= t    = fromIntegral (m `shiftR` e) :% 1
     | t < 8     = fromIntegral (m `shiftR` t) :% (1 `shiftL` (e-t))
     | otherwise = shiftOutZeros (m `shiftR` 8) (e-8)
       where
         !t  = zeros `unsafeAt` (fromIntegral m .&. 255)

 -- Cache of number of trailing 0-bits
 zeros :: Array Int Int
 zeros = listArray (0,255)
             [ 8, 0, 1, 0, 2, 0, 1, 0
             ...
 }}}
 I'm even faster than with `indexIntArray#` (5-10%). With an unboxed array
 for the cache, it's a few percent faster again. Is any kind of unboxed
 array available in GHC.Float?

 Note that on my 32-bit system, for `Float` it's faster to test for
 evenness before going to `shiftOutZeros` while for `Double` it's not (not
 if I `(.&.)` with an `Int64` at least, must try whether `(.&.)`-ing with
 an `Int` is faster).

 For 64-bit systems, `Double` should use the exact same code as `Float`,
 presumably.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4344#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to