[GHC] #10922: String inlining is inconsistent
GHC
ghc-devs at haskell.org
Wed Sep 30 20:23:31 UTC 2015
#10922: String inlining is inconsistent
-------------------------------------+-------------------------------------
Reporter: xnyhps | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: x86_64 | Type of failure: Runtime
(amd64) | performance bug
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): |
-------------------------------------+-------------------------------------
I have the following code:
A.hs:
{{{#!hs
module A where
foo :: String
{-# INLINE foo #-}
foo = "foo"
}}}
B.hs:
{{{#!hs
import A
main = if foo == "foo" then return () else putStrLn "Wrong"
}}}
Compiling this with `-O2` shows the if-statement has not been eliminated
(`"Wrong"` is still part of the output with `-ddump-simpl`).
However, if I rewrite the code to:
A.hs:
{{{#!hs
module A where
foo :: () -> String
{-# INLINE foo #-}
foo () = "foo"
}}}
B.hs:
{{{#!hs
import A
main = if foo () == "foo" then return () else putStrLn "Wrong"
}}}
Then the if-statement disappears and the generated Core has no string
literals left.
Even when the literal can not be eliminated from B it seems GHC is fine
with duplicating it accross two modules if it occurs somewhere inside a
function. But once I make it a top-level expression of type `String`,
inlining it does not happen. I can not think of how this could be working
as intended.
(The case where `A.foo` is `""` seems to work differently, but also does
not get optimized away.)
(This happened to me when rewriting some code that previously used `CPP`
for conditional compilation to using `if System.Info.os == "darwin" then
... else ...` and expecting the other OS cases to get optimized away.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10922>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list