
#16244: Couldn't match kind ‘k1’ with ‘k1’ -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.6.3 (Type checker) | Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program gives a hopelessly confusing error message on GHC 8.6.3 and HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE PolyKinds #-} module Bug where import Data.Kind type Const a b = a type SameKind (a :: k) (b :: k) = (() :: Constraint) class SameKind a b => C (k :: Const Type a) (b :: k) }}} {{{ $ /opt/ghc/8.6.3/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:11:18: error: • Couldn't match kind ‘k1’ with ‘k1’ • In the second argument of ‘SameKind’, namely ‘b’ In the class declaration for ‘C’ | 11 | class SameKind a b => C (k :: Const Type a) (b :: k) | ^ }}} I imagine that the real issue is that `SameKind a b` would force `a :: k`, which would be ill-scoped. But figuring that out from this strange error message requires a lot of thought. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16244 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler