#2281: properFraction implemented with modf primitive?
---------------------------------+------------------------------------------
    Reporter:  guest             |        Owner:              
        Type:  bug               |       Status:  new         
    Priority:  normal            |    Milestone:  6.14.1      
   Component:  libraries/base    |      Version:  6.8.2       
    Keywords:                    |   Difficulty:  Unknown     
          Os:  Unknown/Multiple  |     Testcase:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------
Changes (by igloo):

  * owner:  igloo =>
  * milestone:  6.12.3 => 6.14.1


Comment:

 I've confirmed performance is worse with this program:
 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}

 import Foreign
 import Foreign.C

 main :: IO ()
 main = f

 count :: Int
 count = 100000000

 f :: IO ()
 f = with 0 $ \dptr ->
     do let loop :: Int -> Double -> Double
            loop 0 d = d
            loop n d = modf (realToFrac d) dptr `seq` loop (n - 1) (d +
 0.01)
        print $ loop count 100.456

 g :: IO ()
 g = do let loop :: Int -> Double -> Double
            loop 0 d = d
            loop n d = case properFraction d :: (Int, Double) of
                        (_, frac) -> frac `seq` loop (n - 1) (d + 0.01)
        print $ loop count 100.456

 foreign import ccall "modf" modf :: CDouble -> Ptr CDouble -> CDouble
 }}}

 {{{
 ./f  8.22s user 0.00s system 99% cpu 8.231 total
 ./g  38.35s user 0.03s system 100% cpu 38.382 total
 }}}

 but I'm a bit nervous about the Integral type used affecting the result:
 {{{
     properFraction x
       = case (decodeFloat x)      of { (m,n) ->
         let  b = floatRadix x     in
         if n >= 0 then
             (fromInteger m * fromInteger b ^ n, 0.0)
         else
             case (quotRem m (b^(negate n))) of { (w,r) ->
             (fromInteger w, encodeFloat r n)
             }
         }
 }}}

 I'd suggest the way forward is for someone to make a patch and then turn
 this ticket into a [http://www.haskell.org/haskellwiki/Library_submissions
 library submission].

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2281#comment:11>
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