
#8566: Panic with kindFunResult ------------------------------------+------------------------------------- Reporter: dreixel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- The following program: {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} module Bug where data U (s :: *) = forall k. AA k [U s] data I (u :: U *) (r :: [*]) :: * where A :: I (AA t as) r -- fs unused, but needs to be present for the bug class C (u :: U *) (r :: [*]) (fs :: [*]) where c :: I u r -> I u r instance (C (AA (t (I a ps)) as) ps fs) => C (AA t (a ': as)) ps fs where c A = c undefined }}} crashes a fresh copy of GHC HEAD with the following: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20131126 for i386-unknown-linux): kindFunResult k1{tv a24f} [ssk] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8566 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler