Unexpected boxing in generated code

Hi, I've got an inner loop that I think I can see is strict in the Int argument being passed around, but that GHC 6.6.1 isn't unboxing. In the following example both functions take a GHC.Base.Int, which I think should be an Int#. Rec { f60_rS5 :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Base.Int -> GHC.Base.Int [GlobalId] [Arity 2 NoCafRefs Str: DmdType LL] f60_rS5 = \ (v1_aWH :: GHC.Prim.State# GHC.Prim.RealWorld) (v2_aWI :: GHC.Base.Int) -> case $wccall_r2kv v1_aWH of wild_X2j { (# ds_d1V4, ds1_d1V3 #) -> case ds1_d1V3 of wild1_X2L { __DEFAULT -> f60_rS5 ds_d1V4 v2_aWI; (-1) -> v2_aWI; 10 -> f561_r2kx ds_d1V4 v2_aWI } } f561_r2kx :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Base.Int -> GHC.Base.Int [GlobalId] [Arity 2 NoCafRefs Str: DmdType LL] f561_r2kx = \ (v1_aWm :: GHC.Prim.State# GHC.Prim.RealWorld) (v2_aWn :: GHC.Base.Int) -> case $wccall_r2kv v1_aWm of wild_X2j { (# ds_d1V4, ds1_d1V3 #) -> case ds1_d1V3 of wild1_X2P { __DEFAULT -> case v2_aWn of wild2_a2du { GHC.Base.I# x_a2dw -> case wild1_X2P of wild3_X35 { __DEFAULT -> f60_rS5 ds_d1V4 (GHC.Base.I# (GHC.Prim.+# x_a2dw 1)); 10 -> f561_r2kx ds_d1V4 (GHC.Base.I# (GHC.Prim.+# x_a2dw 1)) } }; (-1) -> v2_aWn } } end Rec } This code comes from a line counting program, I have attached the entire source. My character counting program does infer the correct strictness, although that is based on a single self-recursive function. The largest obvious difference is that the strictness depends on the two functions which call each other - does this impeed GHC's strictness analysis? Thanks Neil

Very curious. It does indeed look as though the strictness analyser is confused; but it should certainly not be confused by mutual recursion. I'll definitely look into it. But don't hold your breath -- it's a very busy fortnight. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On | Behalf Of Neil Mitchell | Sent: 09 July 2007 23:14 | To: glasgow-haskell-users@haskell.org | Subject: Unexpected boxing in generated code | | Hi, | | I've got an inner loop that I think I can see is strict in the Int | argument being passed around, but that GHC 6.6.1 isn't unboxing. In | the following example both functions take a GHC.Base.Int, which I | think should be an Int#. | | Rec { | f60_rS5 :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Base.Int -> GHC.Base.Int | [GlobalId] | [Arity 2 | NoCafRefs | Str: DmdType LL] | f60_rS5 = | \ (v1_aWH :: GHC.Prim.State# GHC.Prim.RealWorld) (v2_aWI :: GHC.Base.Int) -> | case $wccall_r2kv v1_aWH of wild_X2j { (# ds_d1V4, ds1_d1V3 #) -> | case ds1_d1V3 of wild1_X2L { | __DEFAULT -> f60_rS5 ds_d1V4 v2_aWI; | (-1) -> v2_aWI; | 10 -> f561_r2kx ds_d1V4 v2_aWI | } | } | f561_r2kx :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Base.Int -> GHC.Base.Int | [GlobalId] | [Arity 2 | NoCafRefs | Str: DmdType LL] | f561_r2kx = | \ (v1_aWm :: GHC.Prim.State# GHC.Prim.RealWorld) (v2_aWn :: GHC.Base.Int) -> | case $wccall_r2kv v1_aWm of wild_X2j { (# ds_d1V4, ds1_d1V3 #) -> | case ds1_d1V3 of wild1_X2P { | __DEFAULT -> | case v2_aWn of wild2_a2du { GHC.Base.I# x_a2dw -> | case wild1_X2P of wild3_X35 { | __DEFAULT -> f60_rS5 ds_d1V4 (GHC.Base.I# (GHC.Prim.+# x_a2dw 1)); | 10 -> f561_r2kx ds_d1V4 (GHC.Base.I# (GHC.Prim.+# x_a2dw 1)) | } | }; | (-1) -> v2_aWn | } | } | end Rec } | | This code comes from a line counting program, I have attached the | entire source. My character counting program does infer the correct | strictness, although that is based on a single self-recursive | function. The largest obvious difference is that the strictness | depends on the two functions which call each other - does this impeed | GHC's strictness analysis? | | Thanks | | Neil

| I've got an inner loop that I think I can see is strict in the Int | argument being passed around, but that GHC 6.6.1 isn't unboxing. In the | following example both functions take a GHC.Base.Int, which I think | should be an Int#. OK this is an interesting one. Here's the smallest program that demonstrates the problem. foreign import ccall unsafe "stdio.h getchar" getchar :: IO CInt f56 :: State# RealWorld -> Int -> Int f56 s v2 = case (unIO getchar s) of (# s' , v6 #) -> case v2 of I# _ -> f56 s' v2 GHC says this is lazy in v2, which it obviously isn't. Why? Because there's a special hack (introduced after an earlier bug report) in the strictness analyser to account for the fact that a ccall might exit the program. Suppose instead of calling 'getchar' we called 'exit'! Then f56 is not strict in v2 any more. Here was a larger program that demonstrated the problem: do { let len = <expensive> ; ; when (...) (exitWith ExitSuccess) ; print len } Suppose exitWith doesn't exit; it loops or returns. Then 'len' is sure to be evaluated, and GHC will evaluate it before the 'when'. The hack is in the demand analyser, to make it believe that any I/O operation (including getchar!) might exit instead of returning. OK, so that's the reason you aren't getting proper strictness in your inner loop. What to do about it? It would be easy to revert to the non-hack situation, in which case 'len' might well be evaluated in the program above, even in the program above. To make the program sufficiently lazy you could write do { let len = <expensive> ; ; when (...) (exitWith ExitSuccess) ; lazy (print len) } Here 'lazy' is a (documented) function that makes its argument appear to be evaluated lazily, so far as the demand analyser is concerned. But this is horribly non-compositional. ANYWHERE you say do { a; b; c } and b might exit, then you should really say 'lazy c'. One could imagine an analysis for "definitely does not exit". But it only really makes sense for IO-ish things. In short, it's hard to see a beautiful solution. Does anyone else have ideas? Simon

Hi Simon,
OK this is an interesting one. Here's the smallest program that demonstrates the problem.
foreign import ccall unsafe "stdio.h getchar" getchar :: IO CInt
f56 :: State# RealWorld -> Int -> Int f56 s v2 = case (unIO getchar s) of (# s' , v6 #) -> case v2 of I# _ -> f56 s' v2
GHC says this is lazy in v2, which it obviously isn't. Why? Because there's a special hack (introduced after an earlier bug report) in the strictness analyser to account for the fact that a ccall might exit the program. Suppose instead of calling 'getchar' we called 'exit'! Then f56 is not strict in v2 any more.
One could imagine an analysis for "definitely does not exit". But it only really makes sense for IO-ish things.
Why not demand that all unsafe foreign imports do not exit the program? If your foreign call does exit the program, then its unlikely to be performance critical. All unsafe FFI functions can then have their strictness analysed as before. Thanks Neil

Simon Peyton-Jones wrote:
| I've got an inner loop that I think I can see is strict in the Int | argument being passed around, but that GHC 6.6.1 isn't unboxing. In the | following example both functions take a GHC.Base.Int, which I think | should be an Int#.
OK this is an interesting one. Here's the smallest program that demonstrates the problem.
foreign import ccall unsafe "stdio.h getchar" getchar :: IO CInt
f56 :: State# RealWorld -> Int -> Int f56 s v2 = case (unIO getchar s) of (# s' , v6 #) -> case v2 of I# _ -> f56 s' v2
GHC says this is lazy in v2, which it obviously isn't. Why? Because there's a special hack (introduced after an earlier bug report) in the strictness analyser to account for the fact that a ccall might exit the program. Suppose instead of calling 'getchar' we called 'exit'! Then f56 is not strict in v2 any more.
Here was a larger program that demonstrated the problem:
do { let len = <expensive> ; ; when (...) (exitWith ExitSuccess) ; print len }
Suppose exitWith doesn't exit; it loops or returns. Then 'len' is sure to be evaluated, and GHC will evaluate it before the 'when'.
exitWith in fact doesn't exit: it raises the exit exception, which is caught by the top-level exception handler, which finally arranges to exit. So I imagine the strictness analyser inferred that exitWith returns bottom, and hence it was justified in evaluating len first. This doesn't seem specific to exit, to me. Throwing any exception would trigger this behaviour. Indeed, since we're in the IO monad, I might reasonably expect to have greater control over the evaluation order, and perhaps GHC is right - the strictness analyser should not cause something to be evaluated earlier than normal if that means moving it past a possible effect. In fact this behaviour seems to be essential if we are to be able to use lazy I/O in a sensible way, because otherwise lazy I/O can be evaluated earlier than we expect: do s <- getContents putStr "prompt:"; hFlush stdout case s of ... We are sure to evaluate s, but we better not do it before the putStr (I'm sure the strictness analyser won't do this right now, because it won't infer that putStr returns, but imagine some simpler IO instead). I'm not quite sure what to make of this. On the one hand it's ugly, because we're forced into an evaluation order. But even if it weren't for lazy I/O, I am tempted to think that the IO monad ought to restrict evaluation order, if only so that we can have more control when we want it. So perhaps GHC is doing the right thing. Cheers, Simon
participants (3)
-
Neil Mitchell
-
Simon Marlow
-
Simon Peyton-Jones