#5001: makeCorePair: arity missing
---------------------------------+------------------------------------------
    Reporter:  maeder            |        Owner:                                
   
        Type:  bug               |       Status:  infoneeded                    
   
    Priority:  high              |    Milestone:  7.2.1                         
   
   Component:  Compiler          |      Version:  7.0.2                         
   
    Keywords:                    |     Testcase:                                
   
   Blockedby:                    |   Difficulty:                                
   
          Os:  Unknown/Multiple  |     Blocking:                                
   
Architecture:  Unknown/Multiple  |      Failure:  Incorrect warning at 
compile-time
---------------------------------+------------------------------------------
Changes (by michalt):

 * cc: michal.terepeta@… (added)


Comment:

 While checking another bug I've come across this one. Small example:
 {{{
 module M1 where

 class MyEnum a where
   myEnum :: [a]

 instance MyEnum () where
   {-# INLINABLE myEnum #-}
   myEnum = [()]
 }}}
 {{{
 module M2 where

 import M1

 {-# SPECIALISE myEnum  :: [()] #-}
 }}}
 Compiling with HEAD gives:
 {{{
 ~/bugs/ghc/4227 0 > ~/dev/ghc/inplace/bin/ghc-stage2 --make -O -fforce-
 recomp M2
 [1 of 2] Compiling M1               ( M1.hs, M1.o )
 [2 of 2] Compiling M2               ( M2.hs, M2.o )
 makeCorePair: arity missing myEnum{v dcc} [lid]
 }}}
 Interestingly if I move the SPECIALISE pragma into `M1` module, there is
 no
 warning:
 {{{
 module M1 where

 class MyEnum a where
   myEnum :: [a]

 instance MyEnum () where
   {-# INLINABLE myEnum #-}
   myEnum = [()]

 {-# SPECIALISE myEnum  :: [()] #-}
 }}}
 {{{
 ~/bugs/ghc/4227 0 > ~/dev/ghc/inplace/bin/ghc-stage2 --make -O -fforce-
 recomp M1
 [1 of 1] Compiling M1               ( M1.hs, M1.o )
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5001#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

Reply via email to