
#11520: GHC falls into a hole -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE RankNTypes, PolyKinds, TypeInType, GADTs, UndecidableSuperClasses #-} module Play where import GHC.Types hiding (TyCon) data TyCon (a :: k) = TyCon data TypeRep (a :: k) where TypeCon :: forall (a :: k). TyCon a -> TypeRep k -> TypeRep a TypeApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep a -> TypeRep b -> TypeRep (a b) class Typeable k => Typeable (a :: k) where typeRep :: TypeRep a data Compose (f :: k1 -> *) (g :: k2 -> k1) (a :: k2) = Compose (f (g a)) composeTyCon :: TyCon Compose composeTyCon = TyCon Fingerprint "Compose" instance (Typeable f, Typeable (g :: k), Typeable k) => Typeable (Compose f g) where typeRep = TypeApp (TypeApp (TypeCon composeTyCon typeRep) typeRep) typeRep instance (Typeable f, Typeable g, Typeable a) => Typeable (Compose f g a) where typeRep = TypeApp (TypeApp (TypeApp (TypeCon composeTyCon typeRep) typeRep) typeRep) typeRep }}} fails with {{{ λ> :load Bug.hs [1 of 1] Compiling Play ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160122 for x86_64-unknown-linux): fvProv falls into a hole {abet} Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11520 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler