
#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 Resolution: | Keywords: TypeInType, | TypeFamilies 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => TypeInType, TypeFamilies Comment: The `-ddump-tc-trace` panic is an old GHC 8.4.3 bug that has since been fixed. (I can't recall if there was ever a ticket to track this.) I wasn't able to reproduce the infinite loop until I added some more language extensions (`TypeInType` and `TypeFamilies`): {{{#!hs {-# LANGUAGE DataKinds, ExistentialQuantification, GADTs, PolyKinds, TypeOperators #-} {-# LANGUAGE TypeInType, TypeFamilies #-} 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) 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))) }}} This still loops when compiled even on 8.6 and HEAD. I wonder if there is any relationship between this ticket and #15473... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15552#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler