[GHC] #4870: Compiler panic with SPECIALIZE pragma on function from imported module

2010-12-29 Thread GHC
#4870: Compiler panic with SPECIALIZE pragma on function from imported module
-+--
Reporter:  dreixel   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Component:  Compiler
 Version:  7.0.1 |Keywords:  
Testcase:|   Blockedby:  
  Os:  Unknown/Multiple  |Blocking:  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
-+--
 Consider the following two modules:
 {{{
 module Test1 where

 class C a where c :: a -> a

 {-# INLINE f #-}
 f :: (C a) => a
 f = c f
 }}}
 {{{
 module Test2 where

 import Test1

 data D

 instance C D

 {-# SPECIALIZE f :: D #-}
 }}}

 ghc-7.0.1 invoked with -O Test2 results in
 {{{
 [1 of 2] Compiling Test1( Test1.hs, Test1.o )
 [2 of 2] Compiling Test2( Test2.hs, Test2.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.0.1 for i386-unknown-mingw32):
 dsImpSpecs main:Test1.f{v r2} [gid]
 }}}

 This is a highly simplified example of a desired rewrite rule in the
 generic programming library Multirec. Note that there is no problem if the
 code is all in the same module.

-- 
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] #4870: Compiler panic with SPECIALIZE pragma on function from imported module

2010-12-29 Thread GHC
#4870: Compiler panic with SPECIALIZE pragma on function from imported module
-+--
Reporter:  dreixel   |Owner:  
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.0.3   
   Component:  Compiler  |  Version:  7.0.1   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by igloo):

  * priority:  normal => high
  * milestone:  => 7.0.3


Comment:

 Thanks for the report.

-- 
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] #4870: Compiler panic with SPECIALIZE pragma on function from imported module

2011-01-10 Thread GHC
#4870: Compiler panic with SPECIALIZE pragma on function from imported module
-+--
Reporter:  dreixel   |Owner:  
Type:  bug   |   Status:  merge   
Priority:  high  |Milestone:  7.0.3   
   Component:  Compiler  |  Version:  7.0.1   
Keywords:| Testcase:  deSugar/should_compile/T4870
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonpj):

  * status:  new => merge
  * testcase:  => deSugar/should_compile/T4870


Comment:

 Thanks for the example.  Fixed by
 {{{
 Wed Jan  5 00:27:12 GMT 2011  simo...@microsoft.com
   * Fix Trac #4870: get the inlining for an imported INLINABLE Id

   We need the unfolding even for a *recursive* function (indeed
   that's the point) and I was using the wrong function to get it
   (idUnfolding rather than realIdUnfolding).

 M ./compiler/deSugar/DsBinds.lhs -6 +7
 }}}
 Please merge to 7.0 branch

 Simon

-- 
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] #4870: Compiler panic with SPECIALIZE pragma on function from imported module

2011-01-11 Thread GHC
#4870: Compiler panic with SPECIALIZE pragma on function from imported module
---+
  Reporter:  dreixel   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  high  |  Milestone:  7.0.3   
 Component:  Compiler  |Version:  7.0.1   
Resolution:  fixed |   Keywords:  
  Testcase:  deSugar/should_compile/T4870  |  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by igloo):

  * status:  merge => closed
  * resolution:  => fixed


Comment:

 Merged.

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