Erratic failure to specialize function

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?

On Sun, Dec 18, 2011 at 2:57 PM, Alexey Khudyakov
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:
This is a guess, but based on what I've read the GHC inliner only fires when the function is fully saturated as declared - so if you declare a function with one argument to the left of the '=' symbol, the inliner only then inlines when it is applied to one value. This means that the un-inlined function is passed to criterion in the first case, but not the second. Does adding a SPECIALIZE pragma help? Antoine
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?
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On Mon, Dec 19, 2011 at 12:26 AM, Antoine Latter
On Sun, Dec 18, 2011 at 2:57 PM, Alexey Khudyakov
wrote: 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:
This is a guess, but based on what I've read the GHC inliner only fires when the function is fully saturated as declared - so if you declare a function with one argument to the left of the '=' symbol, the inliner only then inlines when it is applied to one value.
This means that the un-inlined function is passed to criterion in the first case, but not the second.
Yes. That's the case. I've checked the core and indeed in the first case function wasn't inlined.
Does adding a SPECIALIZE pragma help?
Yes. Since GHC have a optimized version it chooses it. So it looks like that functions which must be inlined (e.g. to eliminate dictionaries) should be written with no parameters
variance = \vec -> G.sum vec
This variant gets inlined. Otherwise SPECIALIZE pragma could help. Although it's annoying to write so many pragmas
participants (3)
-
Aleksey Khudyakov
-
Alexey Khudyakov
-
Antoine Latter