
#9574: GHC Panic: No Skolem Info -------------------------------------+------------------------------------- Reporter: ian_mi | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: | Blocked By: None/Unknown | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by monoidal): I reduced the panic to this (to reproduce just run `ghci Bug9574`). It makes 7.9 panic but not 7.8, likely by accident though. {{{ {-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, ScopedTypeVariables, GADTs, RankNTypes #-} module Bug9574 where data KProxy (t :: *) = KProxy data Proxy p class Funct f where type Codomain f :: * instance Funct ('KProxy :: KProxy o) where type Codomain 'KProxy = NatTr (Proxy :: o -> *) data NatTr (c :: o -> *) where M :: (forall (a :: o). Proxy a) -> NatTr (c :: o -> *) p :: forall (c :: o -> *). NatTr c p = M t where M t = undefined :: Codomain ('KProxy :: KProxy o) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9574#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler