[GHC] #12242: panic with complicated type/kind/class expressions

GHC ghc-devs at haskell.org
Wed Jun 29 02:38:30 UTC 2016


#12242: panic with complicated type/kind/class expressions
-------------------------------------+-------------------------------------
           Reporter:  Ashley         |             Owner:
  Yakeley                            |
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Linux
       Architecture:  x86_64         |   Type of failure:  GHC rejects
  (amd64)                            |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 I tried to simplify this as much as I could, but I couldn't boil it down
 further than this:

 {{{#!hs
 -- ghc -O -ddump-hi -ddump-to-file Bug.hs
 {-# LANGUAGE TypeInType #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE GADTs #-}
 module Bug where
 {
     import Data.Kind;

     data HetEq (a :: ka) (b :: kb) where
     {
         ReflH :: forall (k :: *) (t :: k). HetEq t t;
     };

     data Rep :: forall (k :: *). k -> * where
     {
         SimpleRep :: forall (k :: *) (a :: k). Rep a;
         ApplyRep :: forall (k1 :: *) (k2 :: *) (p :: k1 -> k2) (a :: k1).
 Rep p -> Rep a -> Rep (p a);
     };

     class TestHetEquality (w :: forall k. k -> *) where
     {
         testHetEquality :: forall (ka :: *) (a :: ka) (kb :: *) (b :: kb).
 w a -> w b -> Maybe (HetEq a b);
     };

     instance TestHetEquality Rep where
     {
         testHetEquality (ApplyRep tfa ta) (ApplyRep tfb tb) = do
         {
             ReflH <- testHetEquality tfa tfb;
             ReflH <- testHetEquality ta tb;
             return ReflH;
         };
         testHetEquality _ _ = Nothing;
     };

     bug :: forall (a :: *). Rep (Maybe a) -> Maybe (Rep a);
     bug (ApplyRep tf ta) = case testHetEquality tf SimpleRep of
     {
         Just ReflH  -> Just ta;
         Nothing -> Nothing;
     };
     bug _ = Nothing;
 }
 }}}

 You'll need `-O` and `-ddump-hi` to trigger it.

 {{{
 $ stack exec -- ghc -O -ddump-hi -ddump-to-file Bug.hs
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-unknown-linux):
         pprIfaceCo

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

 }}}

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


More information about the ghc-tickets mailing list