#3738: Typechecker floats stuff out of INLINE right hand sides
---------------------------------+------------------------------------------
Reporter: rl | Owner: igloo
Type: bug | Status: new
Priority: normal | Milestone: 7.0.1
Component: Compiler | Version: 6.13
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
Changes (by simonpj):
* owner: => igloo
Comment:
Ian: could you turn Romans's comment immediately above into a test? The
code I get at the moment for 'bar' is
{{{
T3738b.bar =
\ (x_aaz :: GHC.Types.Int) ->
let {
a_smr [Dmd=Just L] :: GHC.Types.Int
[LclId, Str=DmdType]
a_smr =
case x_aaz of _ { GHC.Types.I# x1_ajM ->
GHC.Types.I# (GHC.Prim.+# (GHC.Prim.+# x1_ajM 1) 2)
} } in
letrec {
xs_smt [Occ=LoopBreaker] :: [GHC.Types.Int]
[LclId, Str=DmdType]
xs_smt = GHC.Types.: @ GHC.Types.Int a_smr xs_smt; } in
xs_smt
}}}
Note the nice loop for `xs_smt`.
To test that this stays working, here's a test:
{{{
module T3738a where
foo :: Num a => a -> [a]
{-# INLINE foo #-}
foo x = map (+1) (repeat x)
-------------------------
module Main where
import T3738a
bar :: Int -> [Int]
{-# INLINE bar #-}
bar x = map (+2) (foo x)
main = print (bar 2 !! 10000)
}}}
Running the program with `+RTS -sstderr` I get
{{{
-- With ghc 6.12:
./T3738 +RTS -sstderr
5
953,088 bytes allocated in the heap
-- With HEAD:
./T3738 +RTS -sstderr
5
60,368 bytes allocated in the heap
}}}
That seems like a big enough difference that the test could spot it.
Ian, could you add that? Thanks.
Simon
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3738#comment:8>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs