[Haskell-cafe] Inline makes program slow?

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Sat Mar 29 02:09:22 UTC 2014


On 29 March 2014 12:43, Kai Zhang <kai at kzhang.org> wrote:
> Hi cafe,
>
> Inline sometimes can cause problems, at least in following case:
>
> import qualified Data.Vector as V
> import Data.List
>
> f ∷ String → (String → Int → Char) → [Int] → String
> f str g idx = map (g str) idx
>
> h ∷ String → Int → Char
> {-# INLINE h #-}
> h s i = (V.fromList $ sort s) V.! i
>
> slow ∷ String → [Int] → String
> slow str = f str h
>
> fast ∷ String → [Int] → String
> fast str = map ((V.fromList $ sort str) V.!)
>
> main = do
>     let testString = replicate 100000 'a'
>         iterations = replicate 1000 100
>     putStrLn $ fast testString iterations
>     putStrLn $ slow testString iterations
>
> Without inline (remove the inline pragma), "slow" would be much faster. I
> suspect this is because ghc can build a "persistent structure" for the
> partial applied function. After inline, each call of "g" will try to build a
> new vector. How can I tell ghc not to inline some specific functions? Or are
> there other ways to resolve this issue?

There's the NOINLINE and INLINEABLE pragmas.

Though I'm going through some of my own code where I waved the
INLINE-hammer around rather heavily only to find that whilst it
doesn't make much of a difference on my main x86_64 machine, on the
x86 laptop I tested it on it made the code much slower.  So I'm also
interested in finding better ways of determining where and when INLINE
is helpful (rather than blindly removing some INLINEs and re-profiling
to see what difference it makes, as in many cases it *does* require
the INLINE for performance).

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



-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list