Inscrutable error message from PolyKinds (should it be in GHC202X?)

I love the idea of GHC2021, but I've just discovered that PolyKinds, which is part of it, leads to inscrutable error messages. Firstly, a scrutable error message, without PolyKinds: {-# LANGUAGE GHC2021 #-} {-# LANGUAGE NoPolyKinds #-} -- Error: • No instance for (Foldable t) arising from a use of -- ‘length’ foo :: t a -> Int foo = length Good. I know exactly how to fix that. Now the inscrutable message: {-# LANGUAGE GHC2021 #-} -- • Couldn't match kind ‘k’ with ‘*’ -- When matching types -- t0 :: * -> * -- t :: k -> * -- Expected: t a -> Int -- Actual: t0 a0 -> Int -- ‘k’ is a rigid type variable bound by -- the type signature for: -- foo :: forall {k} (t :: k -> *) (a :: k). t a -> Int -- at /tmp/bar.hs:3:1-17 -- • In the expression: length -- In an equation for ‘foo’: foo = length -- • Relevant bindings include -- foo :: t a -> Int (bound at /tmp/bar.hs:4:1) foo :: t a -> Int foo = length What? Non-expert users will experience much puzzlement. (PolyKinds tries to generalise the kind of `a` and fails, because the use of `length` restricts it to `Type`.) Should PolyKinds really be in GHC202X? Tom

Thanks for this program, Tom. I’d be happy to hire a PhD student in Edinburgh, at Heriot-Watt University on improving this. Best, Jur
On 23 Jan 2023, at 13:56, Tom Ellis
wrote: I love the idea of GHC2021, but I've just discovered that PolyKinds, which is part of it, leads to inscrutable error messages. Firstly, a scrutable error message, without PolyKinds:
{-# LANGUAGE GHC2021 #-} {-# LANGUAGE NoPolyKinds #-}
-- Error: • No instance for (Foldable t) arising from a use of -- ‘length’ foo :: t a -> Int foo = length
Good. I know exactly how to fix that. Now the inscrutable message:
{-# LANGUAGE GHC2021 #-}
-- • Couldn't match kind ‘k’ with ‘*’ -- When matching types -- t0 :: * -> * -- t :: k -> * -- Expected: t a -> Int -- Actual: t0 a0 -> Int -- ‘k’ is a rigid type variable bound by -- the type signature for: -- foo :: forall {k} (t :: k -> *) (a :: k). t a -> Int -- at /tmp/bar.hs:3:1-17 -- • In the expression: length -- In an equation for ‘foo’: foo = length -- • Relevant bindings include -- foo :: t a -> Int (bound at /tmp/bar.hs:4:1) foo :: t a -> Int foo = length
What? Non-expert users will experience much puzzlement.
(PolyKinds tries to generalise the kind of `a` and fails, because the use of `length` restricts it to `Type`.)
Should PolyKinds really be in GHC202X?
Tom _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

More examples of GHC2021 inclusion of PolyKinds confusing people: * https://discourse.haskell.org/t/different-typeable-constraints-behaviour-in-... * https://stackoverflow.com/q/72329476/15207568 Sometimes it even causes errors where there were none before. Jaro
On 23 Jan 2023, at 14:56, Tom Ellis
wrote: I love the idea of GHC2021, but I've just discovered that PolyKinds, which is part of it, leads to inscrutable error messages. Firstly, a scrutable error message, without PolyKinds:
{-# LANGUAGE GHC2021 #-} {-# LANGUAGE NoPolyKinds #-}
-- Error: • No instance for (Foldable t) arising from a use of -- ‘length’ foo :: t a -> Int foo = length
Good. I know exactly how to fix that. Now the inscrutable message:
{-# LANGUAGE GHC2021 #-}
-- • Couldn't match kind ‘k’ with ‘*’ -- When matching types -- t0 :: * -> * -- t :: k -> * -- Expected: t a -> Int -- Actual: t0 a0 -> Int -- ‘k’ is a rigid type variable bound by -- the type signature for: -- foo :: forall {k} (t :: k -> *) (a :: k). t a -> Int -- at /tmp/bar.hs:3:1-17 -- • In the expression: length -- In an equation for ‘foo’: foo = length -- • Relevant bindings include -- foo :: t a -> Int (bound at /tmp/bar.hs:4:1) foo :: t a -> Int foo = length
What? Non-expert users will experience much puzzlement.
(PolyKinds tries to generalise the kind of `a` and fails, because the use of `length` restricts it to `Type`.)
Should PolyKinds really be in GHC202X?
Tom _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Mon, Jan 23, 2023 at 03:05:52PM +0100, J. Reinders wrote:
More examples of GHC2021 inclusion of PolyKinds confusing people:
* https://discourse.haskell.org/t/different-typeable-constraints-behaviour-in-... * https://stackoverflow.com/q/72329476/15207568
Sometimes it even causes errors where there were none before.
Great evidence! Thanks for linking it.

On Mon, Jan 23, 2023 at 02:18:22PM +0000, Tom Ellis wrote:
On Mon, Jan 23, 2023 at 03:05:52PM +0100, J. Reinders wrote:
More examples of GHC2021 inclusion of PolyKinds confusing people:
* https://discourse.haskell.org/t/different-typeable-constraints-behaviour-in-... * https://stackoverflow.com/q/72329476/15207568
Sometimes it even causes errors where there were none before.
Great evidence! Thanks for linking it.
A related discussion amongst the GHC steering committee: https://mail.haskell.org/pipermail/ghc-steering-committee/2022-July/002812.h...
participants (3)
-
Hage, J. (Jurriaan)
-
J. Reinders
-
Tom Ellis