[GHC] #8066: Compiler Panic When Using Instance Derivation With Singletons

GHC ghc-devs at haskell.org
Tue Jul 16 22:01:41 CEST 2013


#8066: Compiler Panic When Using Instance Derivation With Singletons
------------------------------------+-------------------------------------
       Reporter:  tvynr             |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  Compiler          |           Version:  7.6.3
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 The following code causes a compiler panic:

 {{{
 {-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances,
 FlexibleInstances, TemplateHaskell, GADTs, TypeFamilies, DataKinds,
 KindSignatures #-}

 module Example
 ( UnqualifiedTVar(..)
 , QualifiedTVar(..)
 , TVar(..)
 , QVar
 , UVar
 , TQual(..)
 ) where

 import GHC.TypeLits

 import qualified Data.Set as Set

 type Identifier = String
 type Span = (Int,Int)

 data QualForm
   = UnqualifiedTVar
   | QualifiedTVar
   deriving (Eq, Ord, Read, Show)

 data instance Sing (f :: QualForm) where
   UnqualifiedTVarS :: Sing UnqualifiedTVar
   QualifiedTVarS :: Sing QualifiedTVar

 instance Eq (Sing (a::QualForm)) where
   (==) = undefined

 instance Ord (Sing (a::QualForm)) where
   compare = undefined

 instance SingI UnqualifiedTVar where
   sing = UnqualifiedTVarS

 instance SingI QualifiedTVar where
   sing = QualifiedTVarS

 data TVar (a :: QualForm)
   = TVar (Sing a) Int [Span]
   deriving (Eq, Ord, Show)

 type QVar = TVar QualifiedTVar
 type UVar = TVar UnqualifiedTVar

 data AnyVar
   = SomeQVar QVar
   | SomeUVar UVar

 anyVar :: TVar (a :: QualForm) -> AnyVar
 anyVar a =
   let (TVar s _ _) = a in
   case fromSing s of
     UnqualifiedTVarS -> SomeUVar a
     QualifiedTVarS -> SomeQVar a
 }}}

 This has been tested on GHC 7.6.1 and GHC 7.6.3; both give an error
 message such as

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.6.1.20121207 for i386-unknown-linux):
         find_thing APromotionErr FamDataConPE
 }}}

 This problem seems to have something to do with instance derivation;
 removing the instances for Eq and Ord causes the problem to go away.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8066>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler




More information about the ghc-tickets mailing list