Erratic failure to specialize function

Alexey Khudyakov alexey.skladnoy at gmail.com
Sun Dec 18 20:57:09 CET 2011


Hello!


I've found a puzzling performance problem with code which uses vector
library and relies heavily on GHC to perform inlining and
specialization. In some cases compiler refuses to specialize function
and just copies there generic version which is slow.

Here is smallest test case I've manages to make:


file 'test.hs'

 > import Criterion.Main
 > import qualified Data.Vector.Unboxed as U
 > import Boundary
 >
 > sample :: U.Vector Double
 > sample = U.replicate 10000 0
 >
 > main = defaultMain
 >   [ bench "eta" $ nf variance sample
 >   , bench "lambda" $ nf (\x -> variance x) sample
 >   ]

file 'Boundary.hs'

 > {-# LANGUAGE FlexibleContexts #-}
 > module Boundary where
 > import qualified Data.Vector.Generic as G
 >
 > variance :: (G.Vector v Double)
 >          => v Double -> Double
 > variance vec = G.sum vec
 > {-# INLINE variance #-}

Here is benchmarking results:

benchmarking eta    - mean: 220.8042 us
benchmarking lambda - mean: 24.31309 us

If variance is moved to the test.hs file or eta reduced or written
as lambda: varance = \vec -> G.sum vec difference goes away.
What causes such behavior?





More information about the Glasgow-haskell-users mailing list