
#15079: GHC HEAD regression: cannot instantiate higher-rank kind -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Now that I have a better understanding of why this is failing, here's a simpler program which demonstrates the issue (this typechecks on GHC 8.4.2, but not HEAD): {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind newtype Foo (f :: forall (a :: Type). a -> Type) = MkFoo (f Int) data InferredProxy a = MkInferredProxy foo :: Foo InferredProxy foo = MkFoo MkInferredProxy }}} {{{ $ ~/Software/ghc/inplace/bin/ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:11:13: error: • Kind mismatch: cannot unify (f0 :: forall a. a -> *) with: InferredProxy :: forall k. k -> * Their kinds differ. Expected type: f0 * Int Actual type: InferredProxy Int • In the first argument of ‘MkFoo’, namely ‘MkInferredProxy’ In the expression: MkFoo MkInferredProxy In an equation for ‘foo’: foo = MkFoo MkInferredProxy | 11 | foo = MkFoo MkInferredProxy | ^^^^^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15079#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler