Unexpected failure to inline, even with pragma

p.k.f.holzenspies at utwente.nl p.k.f.holzenspies at utwente.nl
Thu May 1 12:59:23 UTC 2014


Dear GHC-ers,

It seems I do not quite understand the behaviour of the inliner. Consider these two modules:


module Foo.Bar where

foo :: Char -> IO ()
foo = putChar

{-# INLINE bar #-}
bar :: String -> IO ()
bar = mapM_ foo



module Main where
import Foo.Bar
main = bar "done"


I would expect the inliner to produce at least (considering the pragma)

main = mapM_ foo "done"

or maybe even

main=mapM_ putChar "done"

However, when I compile this code, that inlining does not seem to happen:


$ ghc -ddump-inlinings -fforce-recomp Main.hs
[1 of 2] Compiling Foo.Bar          ( Foo/Bar.hs, Foo/Bar.o )
Inlining done: Foo.Bar.foo
[2 of 2] Compiling Main             ( Main.hs, Main.o )
Linking Main ...


Indeed, when I use -ddump-simpl, ghc reports:



==================== Tidy Core ====================
Result size of Tidy Core = {terms: 7, types: 5, coercions: 0}

Main.main :: GHC.Types.IO ()
[GblId, Str=DmdType]
Main.main = Foo.Bar.bar (GHC.CString.unpackCString# "done"#)

:Main.main :: GHC.Types.IO ()
[GblId, Str=DmdType]
:Main.main = GHC.TopHandler.runMainIO @ () Main.main



Can anyone explain why Foo.Bar.bar isn't inlined in Main.main?

Regards,
Philip


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/ghc-devs/attachments/20140501/db4ee64d/attachment.html>


More information about the ghc-devs mailing list