[Haskell-cafe] Inscrutable error message from PolyKinds (should it be in GHC202X?)

Tom Ellis tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk
Mon Jan 23 13:56:41 UTC 2023


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


More information about the Haskell-Cafe mailing list