#2787: Panic (core lint failure) with type synonym in GHC 6.10.1
---------------------------+------------------------------------------------
    Reporter:  BenMoseley  |       Owner:                         
        Type:  bug         |      Status:  new                    
    Priority:  normal      |   Component:  Compiler (Type checker)
     Version:  6.10.1      |    Severity:  major                  
    Keywords:              |    Testcase:                         
Architecture:  x86         |          Os:  Windows                
---------------------------+------------------------------------------------
 This causes a panic:

 {{{
 {-# LANGUAGE TypeFamilies, GADTs #-}
 module GHCBug (
   PVR(..),
   Core(..),
   analyseCore
 )
 where

 data Core a where Ctr :: Core Double
 data PVR a = PVR a deriving (Eq, Show)


 class Sub a where
     type AssocSyn a :: * -> *

 instance Sub Double where
     type AssocSyn Double = PVR


 analyseCore :: Core a -> ((AssocSyn a) a)
 analyseCore Ctr = pvr
   where
     -- GHC panics if we use the below as the type sig for 'pvr'
     pvr :: PVR ~ AssocSyn a => (AssocSyn a) a
     -- pvr :: (AssocSyn a) a
     pvr = undefined

 main :: IO ()
 main = print "ok"
 }}}

 The basic compiler panic is:
 {{{
 c:/ws/main/depot/QA/EDG/EDG_priv/FPF_Dev.br/src $ ghc -main-is GHCBug
 ~/GHCBug.hs
 ghc.exe: panic! (the 'impossible' happened)
   (GHC version 6.10.1 for i386-unknown-mingw32):
         initC: srt_lbl

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 The core lint failure part is:
 {{{
 *** Checking old interface for main:GHCBug:
 *** Parser:
 *** Renamer/typechecker:
 *** Desugar:
     Result size = 199
 *** Core Lint Errors: in result of Desugar ***
 {-# LINE 21 "F:\ME\GHCBug.hs #-}:
     [RHS of pvr_awa :: GHCBug.AssocSyn
                          GHC.Types.Double GHC.Types.Double]
     pvr_afN is out of scope
 *** Offending Program ***
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2787>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to