
duncan.coutts:
On Fri, 2008-05-23 at 21:24 +0200, Henning Thielemann wrote:
On Fri, 23 May 2008, Bulat Ziganshin wrote:
Hello Henning,
Friday, May 23, 2008, 8:31:24 PM, you wrote:
would guarantee speed in every case. Or I can SPECIALISE the function, then the function will only be called, but with polymorphism overhead eliminated. This would only work for a restricted range of types. I'd like to have a pragma, that tells GHC to specialise a function for every type it is called with.
me too. btw, this already present in jhc. inlining doesn't work in any complex case since recursive functions can't be inlined
GHC inlines recursive functions, too, otherwise it could not turn 'foldl' and friends into plain machine loops.
Actually ghc's definition of foldl is not recursive, though it does of course contain a local recursion:
foldl :: (a -> b -> a) -> a -> [b] -> a foldl f z xs = lgo z xs where lgo z [] = z lgo z (x:xs) = lgo (f z x) xs
The lgo recursive call is then specialised at the call site and we can get good code.
As I understand it, if foldl was written in the standard directly way then ghc would not inline it. So we have to manually apply the static argument transformation. You'll see that foldr is written in the same way.
Similar for length et al. These worker/wrapper things inline quite happily: module B where mylength :: [a] -> Int mylength = go 0 where go :: Int -> [a] -> Int go n [] = n go n (_:xs) = go (n+1) xs {-# INLINE mylength #-} module A where import B main = print (mylength (enumFromTo 1 (10::Int))) ------------------------------------------------------------------------ And it is all inlined into A.hs: A.lvl2 = case A.go1 @ Int A.lvl A.lvl1 of w_axy { I# ww_axA -> $wshowSignedInt 0 ww_axA ([] @ Char) } A.go1 :: forall a1_a5n. Int -> [a1_a5n] -> Int A.go1 = \ (@ a1_a7b) (n_a5p :: Int) (ds_d9N :: [a1_a7b]) -> case ds_d9N of wild_B1 { [] -> n_a5p; : ds1_d9O xs_a5s -> A.go1 @ a1_a7b (case n_a5p of wild1_aqC { I# x_aqE -> I# (+# x_aqE 1) }) xs_a5s -- Don