Re: [GHC] #5252: UNPACK without optimisation leads to panic

2012-11-06 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:
  
  Type:  bug   | Status:  
closed  
  Priority:  normal|  Milestone:  7.6.2 
  
 Component:  Compiler  |Version:  7.6.1 
  
Resolution:  fixed |   Keywords:
  
Os:  Unknown/Multiple  |   Architecture:  
Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  
Unknown 
  Testcase:  deSugar/should_compile/T5252, T5252Take2  |  Blockedby:
  
  Blocking:|Related:
  
---+
Changes (by pcapriotti):

  * status:  merge = closed
  * resolution:  = fixed


Comment:

 Merged as 8b4fee353aa6bfcd08d7ea5ab8b8cc2b526e26f3.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:8
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2012-09-27 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:
  
  Type:  bug   | Status:  merge 
  
  Priority:  normal|  Milestone:  7.6.2 
  
 Component:  Compiler  |Version:  7.6.1 
  
Resolution:|   Keywords:
  
Os:  Unknown/Multiple  |   Architecture:  
Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  
Unknown 
  Testcase:  deSugar/should_compile/T5252, T5252Take2  |  Blockedby:
  
  Blocking:|Related:
  
---+
Changes (by igloo):

  * milestone:  = 7.6.2


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:7
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2012-09-18 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:
  
  Type:  bug   | Status:  merge 
  
  Priority:  normal|  Milestone:
  
 Component:  Compiler  |Version:  7.6.1 
  
Resolution:|   Keywords:
  
Os:  Unknown/Multiple  |   Architecture:  
Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  
Unknown 
  Testcase:  deSugar/should_compile/T5252, T5252Take2  |  Blockedby:
  
  Blocking:|Related:
  
---+
Changes (by simonpj):

  * status:  new = merge
  * testcase:  deSugar/should_compile/T5252 =
   deSugar/should_compile/T5252, T5252Take2


Comment:

 Needs this patch too:
 {{{
 commit ba8fd081ba9b222dd5f93604d7deeaca372e4511
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Mon Sep 17 18:22:10 2012 +0100

 Make the call to chooseBoxingStrategy lazy again

 I made it strict, as an incidental consequence of this patch:

   commit 5bae803a18b17bdb158a7780e6b6ac3c520e5b39
   Author: Simon Peyton Jones simo...@microsoft.com
   Date:   Sat Sep 15 23:09:25 2012 +0100
   Fix UNPACK with -fomit-interface-pragmas.

 But it's very important that chooseBoxingStrategy is lazy, else
 (in bigger programs with lots of recursion in types) GHC can
 loop. This showed up in Data.Sequence; and I think it was making
 haddock loop as well.

 Anyway this patch makes it lazy again.

  compiler/typecheck/TcTyClsDecls.lhs |   34
 +-
  1 file changed, 17 insertions(+), 17 deletions(-)
 }}}
 Regression test added.

 Merge to 7.6 branch.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:6
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2012-09-17 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  deSugar/should_compile/T5252  |  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj@…):

 commit 5bae803a18b17bdb158a7780e6b6ac3c520e5b39
 {{{
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Sat Sep 15 23:09:25 2012 +0100

 Fix UNPACK with -fomit-interface-pragmas.

 We were missing a case, so that you could expose a constructor
 with UNPACKed fields, but the field tpye was trimmed, and hence
 can't be expanded.

 Fixes Trac #5252 (revived)

  compiler/typecheck/TcTyClsDecls.lhs |   29 -
  1 files changed, 16 insertions(+), 13 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:5
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2012-09-15 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  deSugar/should_compile/T5252  |  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

 * cc: qdunkan@… (added)
  * difficulty:  = Unknown
  * status:  closed = new
  * resolution:  fixed =
  * version:  7.0.3 = 7.6.1


Comment:

 Evan Laforge writes (to ghc-users): I have something that looks similar to
 #5252, namely, given these two modules:
 {{{
 % cat Midi.hs
 {-# OPTIONS_GHC -funbox-strict-fields #-}
 module Midi (
 WriteMessage(..)
 , WriteDevice
 -- TODO due ghc bug: http://hackage.haskell.org/trac/ghc/ticket/5252
 -- , WriteDevice(WriteDevice)
 ) where
 import qualified Data.ByteString as ByteString

 data WriteMessage = WriteMessage !WriteDevice
 newtype WriteDevice = WriteDevice ByteString.ByteString

 % cat CoreMidi.hs
 module CoreMidi where
 import qualified Midi

 write_message :: Midi.WriteMessage - IO Bool
 write_message (Midi.WriteMessage _) = return True
 }}}
 If I compile thus I get a compiler crash with GHC 7.6.1
 {{{
 % ghc -c Midi.hs
 % ghc -c CoreMidi.hs
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1 for x86_64-apple-darwin):
 reboxProduct: not a product main:Midi.WriteDevice{tc r2M}
 }}}
 Oddly, if I put `{-# UNPACK #-}` on the strict `WriteDevice` and remove
 `-funbox-strict-fields`, I don't get a crash anymore.  Also, it has to
 be `ByteString` inside, I guess it has to do with the optimization
 `ByteString` applies.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:3
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2012-09-15 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  deSugar/should_compile/T5252  |  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj):

 Quite right.  My fix for #5252 had a bug.  Patch coming.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:4
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2011-06-11 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.0.3   
Resolution:  fixed |   Keywords:  
  Testcase:  deSugar/should_compile/T5252  |  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by simonpj):

  * testcase:  = deSugar/should_compile/T5252


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#comment:2
GHC http://www.haskell.org/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] #5252: UNPACK without optimisation leads to panic

2011-06-10 Thread GHC
#5252: UNPACK without optimisation leads to panic
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.3   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
 Here's a two-module progam
 {{{
 module Foo where
   import Bar
   blah :: S - T
   blah (MkS x _) = x

 module Bar( S(..), T ) where
   data T = MkT Int Int
   data S = MkS {-# UNPACK #-}!T Int
 }}}
 Now with ghc 7.0.3 we get
 {{{
 bash-3.1$ ghc -c Bar.hs
 bash-3.1$ ghc -c Foo.hs
 ghc.exe: panic! (the 'impossible' happened)
   (GHC version 7.0.3 for i386-unknown-mingw32):
 reboxProduct: not a product main:Foo1.T{tc r2}
 }}}
 The problem is that
  * We are compiling with -O so GHC tries to put as little as possible into
 the interface file `Bar.hi`.  And it does not put in T's constructors
 {{{
   data S
   RecFlag NonRecursive
   Generics: no
   = MkS :: Foo1.T - GHC.Types.Int - S
 HasWrapper
 Stricts: {-# UNPACK #-} ! _
 43edb8535d0555fb50e9f93a9c3203bf
   data T
   RecFlag NonRecursive
   Generics: no
   {- abstract -}
 }}}
  * However the pattern match in `Foo` requires that GHC can see the full
 representation for T, becuase it UNPACK's the argument.

  * A workaround is to export `MkT` from `Bar`.

 The solution I am implementing is to ignore UNPACK pragmas when
 `OmitInterfacePragmas` is on.  This flag is the one that causes trimming
 of the exposed constructors.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs