Re: [GHC] #1592: Unexpected boxing in generated code

2009-04-11 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner:  
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  6.10 branch 
   Component:  Compiler  |  Version:  6.6.1   
Severity:  minor |   Resolution:  invalid 
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by igloo):

  * status:  new => closed
  * resolution:  => invalid

Comment:

 I think the conclusion is that this isn't a bug at all, and you can get
 the strictness you want with appropriate bang patterns (or equivalent).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2008-04-14 Thread GHC
#1592: Unexpected boxing in generated code
--+-
 Reporter:  neil  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.6.1  
 Severity:  minor | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by SamB):

 neil, you really need to work on your style ;-). More seriously, maybe
 your compiler should use {{{seq}}} to indicate that it wants things to be
 strict?

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-11-05 Thread GHC
#1592: Unexpected boxing in generated code
--+-
 Reporter:  neil  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.6.1  
 Severity:  minor | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Changes (by igloo):

  * milestone:  => 6.10 branch

Comment:

 Simon's argument that GHC is doing the right thing sounds right to me;
 should we close this bug?

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-23 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Changes (by guest):

  * cc:  [EMAIL PROTECTED], [EMAIL PROTECTED] =>
 [EMAIL PROTECTED], [EMAIL PROTECTED],
 [EMAIL PROTECTED]

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-09 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by simonpj):

 Simon M responds: 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.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-09 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by simonpj):

 Neil reponds:
 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.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-09 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Old description:

> 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?

New description:

 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?

Comment (by simonpj):

 (Written before I'd seen Tim's correct remarks.)  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 =  ;
; when (...) (exitWith ExitSuccess)
; print len }
 }}}
 Suppose exitWith doesn't exit; it loops or returns. Then 'len' is sure to
 be evaluated

Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-06 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Changes (by guest):

  * cc:  [EMAIL PROTECTED] => [EMAIL PROTECTED],
 [EMAIL PROTECTED]

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-06 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by [EMAIL PROTECTED]):

 This actually doesn't have to do with the mutual recursion; it happens
 because of the "IO hack" in the demand analyzer. As per comments in the
 dmdAnalAlt function in DmdAnal.lhs, what's happening is that  the call to
 $wccall_r2kv is being recognized as an IO operation (based on its type);
 because an IO operation might terminate the program in a non-erroneous
 way, it wouldn't be correct to evaluate f60's arguments before the call to
 $wccall_r2kv.

 Now, in this case, $wccall_r2kv is just getchar(), which I don't think
 could possibly terminate the program, so maybe the IO hack needs to be
 made a little bit more specific...

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-06 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by neil):

 For the first paragraph of my report, read:

 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#.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1592: Unexpected boxing in generated code

2007-08-06 Thread GHC
#1592: Unexpected boxing in generated code
-+--
Reporter:  neil  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  minor |   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by neil):

 Simon PJ replied:

 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.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #1592: Unexpected boxing in generated code

2007-08-06 Thread GHC
#1592: Unexpected boxing in generated code
---+
  Reporter:  neil  |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.6.1  
  Severity:  minor |   Keywords: 
Difficulty:  Unknown   | Os:  Unknown
  Testcase:|   Architecture:  Unknown
---+
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?

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs