[GHC] #15552: Infinite loop/panic with an existential type.

GHC ghc-devs at haskell.org
Tue Aug 21 16:08:34 UTC 2018


#15552: Infinite loop/panic with an existential type.
-------------------------------------+-------------------------------------
           Reporter:  howtonotwin    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.1
          Component:  Compiler       |           Version:  8.4.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #14723
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The symptoms of this bug are quite similar to #14723, but I don't know if
 the cause is exactly the same, ergo a new report.

 To reproduce:

 1. Make `T.hs`
 {{{#!hs
 {-# LANGUAGE DataKinds, ExistentialQuantification, GADTs, PolyKinds,
 TypeOperators #-}
 module T where

 import Data.Kind

 data Elem :: k -> [k] -> Type where
   Here :: Elem x (x : xs)
   There :: Elem x xs -> Elem x (y : xs)

 data EntryOfVal (v :: Type) (kvs :: [Type]) = forall (k :: Type).
 EntryOfVal (Elem (k, v) kvs)
 }}}

 2. Compile it with `ghc T.hs -ddump-tc-trace`
 {{{
 # etc.
 checkExpectedKind
   *
   TYPE t_aXd[tau:1]
   <*>_N
 kcLHsQTyVars: not-cusk
   EntryOfVal
   []
   [(k_aW0 :: Type)]
   []
   [k_aW0[sk:1]]
   *ghc: panic! (the 'impossible' happened)
   (GHC version 8.4.3 for x86_64-apple-darwin):
         kcConDecl

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

 3. Append the following to `T.hs` (not minimized, sorry)
 {{{#!hs
 type family EntryOfValKey (eov :: EntryOfVal v kvs) :: Type where
   EntryOfValKey ('EntryOfVal (_ :: Elem (k, v) kvs)) = k
 type family GetEntryOfVal (eov :: EntryOfVal v kvs) :: Elem (EntryOfValKey
 eov, v) kvs where
   GetEntryOfVal ('EntryOfVal e) = e

 type family FirstEntryOfVal (v :: Type) (kvs :: [Type]) :: EntryOfVal v
 kvs where
   FirstEntryOfVal v ((k, v) : _) = 'EntryOfVal Here
   FirstEntryOfVal v (_ : kvs) = 'EntryOfVal (There (GetEntryOfVal
 (FirstEntryOfVal v kvs)))
 }}}

 4. Compile with a plain `ghc T.hs`
     1. Wait until bored, then knock the compiler out of its infinite loop
 by killing it.
 5. Compile again with `ghc T.hs -ddump-tc-trace`
 {{{
 # etc.
 checkExpectedKind
   *
   TYPE t_aYg[tau:1]
   <*>_N
 kcLHsQTyVars: not-cuskghc: panic! (the 'impossible' happened)
   (GHC version 8.4.3 for x86_64-apple-darwin):
         kcConDecl

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

 Found while trying to answer [https://stackoverflow.com/q/51944931/5684257
 this SO question].

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


More information about the ghc-tickets mailing list