[Haskell-cafe] Inline makes program slow?

Kai Zhang kai at kzhang.org
Sat Mar 29 01:43:21 UTC 2014


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?
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140328/9bb20f54/attachment.html>


More information about the Haskell-Cafe mailing list