Erratic failure to specialize function

Antoine Latter aslatter at gmail.com
Sun Dec 18 21:26:19 CET 2011


On Sun, Dec 18, 2011 at 2:57 PM, Alexey Khudyakov
<alexey.skladnoy at gmail.com> 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.

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 at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list