I've performed some experiments in GHCi, and it looks like even for a
simple function (+) (which should be the worst case, since if the
computation is simple, any extra time required to dispatch the call
will show up more strongly in comparison) it doesn't really matter.  I
get essentially the same execution times no matter which of the
definitions below I use, although sometimes one time (apparently at
random) is 2-3 times as large as the others; I presume this is the
garbage collector at work, or something.  Given these results, I'm
inclined to make my function types as general as possible, with
typeclasses galore, and only use pragmas if profiling reveals a good
reason to.

I'm attaching my test code for reference.  Clumsy noob Haskell code
below (I'm still pretty new to Haskell, and this is the first time
I've programmed in a monad):

************************************************************************
TypeClassTest.lhs
Test of what effect (if any) using a typeclass in GHC has on performance
************************************************************************

module TypeClassTest where
import System.CPUTime

l :: [Double]
l = [0.0,1.0..1e5]

Fully specialized:

addDouble :: Double -> Double -> Double
addDouble = (+)

Generic, but with inlining:

{-# INLINE addInline #-}
addInline :: Num a => a -> a -> a
addInline = (+)

Generic, but with specialization:

{-# SPECIALIZE addSpecialize :: Double -> Double -> Double #-}
addSpecialize :: Num a => a -> a -> a
addSpecialize = (+)

Generic, with no compiler pragmas:

addGeneric :: Num a => a -> a -> a
addGeneric = (+)


main :: IO ()
main = do putStrLn $ "Summing " ++ length l ++ " floating-point values in various 
ways..."
          foldTime "Double list with addDouble" addDouble l
          foldTime "Double list with addInline" addInline l
          foldTime "Double list with addSpecialized" addSpecialize l
          foldTime "Double list with addGeneric" addGeneric l
          return ()

foldTime :: String -> (a -> a -> a) -> [a] -> IO a
foldTime desc f l = do start  <- getCPUTime
                       result <- (return $! foldr1 f l)
                       end    <- getCPUTime
                       putStrLn $ "Time for " ++ desc ++ " per list element:  " 
++ show ((end-start) `div` (fromIntegral $ length l))
                       return result

--Grady Lemoine

On 12/29/06, Kirsten Chevalier <[EMAIL PROTECTED]> wrote:
On 12/29/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> i propose you to use INLINE pragma:
>
> {-# INLINE foo #-}
>
> unless your function is recursive. in this case, you should use SPECIALIZE
> pragma:
>
> {-# SPECIALIZE foo :: Double -> Double -> Double #-}
>

I suggest *not* using these pragmas unless a combination of profiling
and reading intermediate code dumps suggests that foo -- and its
un-specialized nature -- is truly a bottleneck. Excessive amounts of
SPECIALIZE pragmas can make your code ugly without actually improving
performance if you optimize prematurely (and I speak from experience).
Think *first*, add pragmas later; again, people on the mailing lists
and IRC channel are usually happy to provide guidance with this.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
"To be free is not to have the power to do anything you like; it is to be able
to surpass the given towards an open future..."--Simone de Beauvoir

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to