
#15076: Typed hole with higher-rank kind causes GHC to panic (No skolem info) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: TypedHoles, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14040, #14880 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another example of this bug, discovered in https://github.com/goldfirere/ghc/issues/57 : {{{#!hs {-# LANGUAGE PolyKinds, MultiParamTypeClasses, GADTs, ScopedTypeVariables, TypeOperators #-} {-# OPTIONS_GHC -fno-warn-redundant-constraints #-} module Super where import Data.Proxy import GHC.Prim class (a ~ b) => C a b data SameKind :: k -> k -> * where SK :: SameKind a b bar :: forall (a :: *) (b :: *). C a b => Proxy a -> Proxy b -> () bar _ _ = const () (undefined :: forall (x :: a) (y :: b). SameKind x y) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15076#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler