
#11635: Missleading error message when using polymorpic kinds -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by phadej): And I found a workaround to make a code compile. It's not usable, but that's probably another issue: {{{ {-# LANGUAGE TypeInType, ImpredicativeTypes, KindSignatures, ExplicitForAll #-} import Data.Kind import Data.Proxy newtype X (a :: forall k. k -> * ) = X { x :: a Bool -> a (*) } -- X { x = \_ -> Proxy :: Proxy (*) } {- fails with: • Couldn't match kind ‘forall k1. k1 -> *’ with ‘forall k. k -> *’ When matching the kind of ‘Proxy’ • In the expression: Proxy :: Proxy * In the ‘x’ field of a record In the expression: X {x = \ _ -> Proxy :: Proxy *} -} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11635#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler