#4081: Strict constructor fields inspected in loop
---------------------------------+------------------------------------------
Reporter: rl | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 7.0.2
Component: Compiler | Version: 6.13
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Runtime performance bug
---------------------------------+------------------------------------------
Comment(by simonpj):
Here's another example that Ben was looking at:
{{{
{-# LANGUAGE BangPatterns #-}
module Foo(foo) where
-- Library Code
---------------------------------------------------------------
data Thing = Manifest !Int | None
getManifestThing :: Thing -> Int
getManifestThing (Manifest t) = t
getManifestThing _ = error "sorry"
loopIt :: (Int -> Int) -> Int -> Int
{-# INLINE loopIt #-}
loopIt f iters
= loopOuter iters
where loopOuter 0 = 0
loopOuter n = loopInner iters + loopOuter (n - 1)
loopInner 0 = 0
loopInner n = f n + loopInner (n - 1)
-- Client Code
----------------------------------------------------------------
foo :: Thing -> Int -> Int
foo t1@(Manifest i) count
= i `seq` go count
where go 0 = 0
go n = loopIt (worker t1 n) count + go (n - 1)
worker :: Thing -> Int -> Int -> Int
worker t x n = getManifestThing t + n + x
}}}
Here we get a loop like this:
{{{
$wfoo :: Thing -> Int# -> Int#
$wfoo =
\ (w_so2 :: Thing) (ww_so5 :: Int#) ->
case w_so2 of _ {
Manifest i_aaX ->
letrec {
$wgo_soj :: Int# -> Int#
$wgo_soj =
\ (ww1_snU :: Int#) ->
case ww1_snU of ds_Xma {
__DEFAULT ->
letrec {
$wloopOuter_son :: Int# -> Int#
$wloopOuter_son =
\ (ww2_snL :: Int#) ->
case ww2_snL of wild1_Xi {
__DEFAULT ->
case ww_so5 of ds1_XlU {
__DEFAULT ->
************************ case i_aaX of _ { I# x_amh ->
letrec {
$wloopInner_sol :: Int# -> Int#
$wloopInner_sol =
\ (ww3_Xo5 :: Int#) ->
case ww3_Xo5 of ds2_Xmo {
__DEFAULT ->
case $wloopInner_sol (-# ds2_Xmo
1)
of ww4_snG { __DEFAULT ->
+# (+# (+# x_amh ds2_Xmo)
ds_Xma) ww4_snG
};
0 -> 0
}; } in
case $wloopInner_sol (-# ds1_XlU 1) of
ww3_snG { __DEFAULT ->
case $wloopOuter_son (-# wild1_Xi 1) of
ww4_snP { __DEFAULT ->
+# (+# (+# (+# x_amh ds1_XlU) ds_Xma)
ww3_snG) ww4_snP
}
}
};
0 -> $wloopOuter_son (-# wild1_Xi 1)
};
0 -> 0
}; } in
case $wloopOuter_son ww_so5 of ww2_snP { __DEFAULT ->
case $wgo_soj (-# ds_Xma 1) of ww3_snY { __DEFAULT ->
+# ww2_snP ww3_snY
}
};
0 -> 0
}; } in
$wgo_soj ww_so5;
None -> lvl_roB `cast` (CoUnsafe Int Int# :: Int ~ Int#)
}
}}}
The "*****" line inspects `i_aaX` inside the loop, but that same `case`
could safely occur right when we unpack the constructor. I think this is
the same issue as the much smaller example above, but I wanted to capture
the example.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4081#comment:5>
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