
#13407: Fix printing of higher-rank kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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 RyanGlScott): Another higher-rank kind pretty-printing oddity: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind type family Foo (a :: Type) :: Type type instance Foo (a :: forall k. k -> Type) = Int }}} {{{ GHCi, version 8.2.0.20170523: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:9:19: error: • Expecting one more argument to ‘a k1’ Expected a type, but ‘a k1’ has kind ‘k1 -> *’ • In the first argument of ‘Foo’, namely ‘(a :: forall k. k -> Type)’ In the type instance declaration for ‘Foo’ | 9 | type instance Foo (a :: forall k. k -> Type) = Int | ^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} The error message mentions `a k1`... how did that `k1` sneak in there? I'm not sure if it's due to the same root cause as the original issue, but thought it was worth mentioning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13407#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler