#1434: Slow conversion from Double to Int
------------------------------------------+---------------------------------
    Reporter:  [EMAIL PROTECTED]  |        Owner:         
        Type:  bug                        |       Status:  new    
    Priority:  normal                     |    Milestone:         
   Component:  libraries/base             |      Version:  6.4.1  
    Severity:  normal                     |   Resolution:         
    Keywords:                             |   Difficulty:  Unknown
          Os:  Linux                      |     Testcase:         
Architecture:  Unknown                    |  
------------------------------------------+---------------------------------
Comment (by [EMAIL PROTECTED]):

 The following example is still certainly not the most compact one.
 The above examples let me assume
 that the difference between {{{round}}} and {{{double2Int}}}
 is eliminated by the optimizer.
 However, when I use {{{Int16}}} instead of {{{Int}}},
 this optimization seems to fail, again.
 {{{
 {-# OPTIONS -O2 #-}
 {-  -package fps -package binary -}
 module Main (main) where

 import System.Time (getClockTime, diffClockTimes, tdSec, tdPicosec)
 import System.Directory (removeFile)

 import qualified Data.ByteString.Lazy as B
 import qualified Data.Binary.Put as Bin

 import Foreign (Int16)

 import GHC.Float (double2Int)



 type Sample = Int16    -- 'truncate' is slow
 -- type Sample = Int     -- 'truncate' is as fast as double2Int


 writeSignalMonoBinaryPut ::
    FilePath -> [Sample] -> IO ()
 writeSignalMonoBinaryPut fileName =
    B.writeFile fileName .
    Bin.runPut .
    mapM_ (Bin.putWord16host . fromIntegral)



 numToSample :: Double -> Sample
 numToSample x =
    -- fromIntegral $ (truncate x :: Int)
    truncate x

 doubleToSample :: Double -> Sample
 doubleToSample x =
    fromIntegral $ double2Int x



 {- * driver -}

 measureTime :: String -> IO () -> IO ()
 measureTime name act =
    do putStr (name++": ")
       timeA <- getClockTime
       act
       timeB <- getClockTime
       let td = diffClockTimes timeB timeA
       print (fromIntegral (tdSec td) +
              fromInteger (tdPicosec td) * 1e-12 :: Double)




 exponential2 :: Double -> Double -> [Double]
 exponential2 k = iterate (k*)


 sawSignalDouble :: Double -> [Double]
 sawSignalDouble halfLife =
    take 200000 (exponential2 halfLife 32767)

 sawSignal16Trunc :: [Sample]
 sawSignal16Trunc =
    map numToSample (sawSignalDouble 0.999)

 sawSignal16LowLevel :: [Sample]
 sawSignal16LowLevel =
    map doubleToSample (sawSignalDouble 0.999001)


 tests :: [(String, FilePath, FilePath -> IO ())]
 tests =
    ("saw double2Int", "saw-double2Int.sw", flip writeSignalMonoBinaryPut
 sawSignal16LowLevel) :
    ("saw round",      "saw-round.sw",      flip writeSignalMonoBinaryPut
 sawSignal16Trunc) :
    []


 main :: IO ()
 main =
    do mapM (\(label, fileName, action) ->
               measureTime label (action fileName))
            tests

       mapM_ (\(_,fileName,_) -> removeFile fileName)
            tests
 }}}

 For {{{type Sample = Int16}}} I get
 {{{
 $ ghc-6.6.1 -package binary RoundTest.hs && a.out
 saw double2Int: 8.7173e-2
 saw round: 0.430843
 }}}
 For {{{type Sample = Int}}} I get
 {{{
 $ ghc-6.6.1 -package binary RoundTest.hs && a.out
 saw double2Int: 8.8279e-2
 saw round: 9.8028e-2
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1434>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to