Rather terrible error message due to excessive kind polymorphism
When fixing up cassava
for GHC 8.0 I found I needed to enable PolyKinds
due to an unrelated change (namely in order to apply Proxy
to something of kind GHC.Generics.Meta
, which will be quite a common refactoring in 8.0) encountered a rather vexing error.
Consider this,
{-# LANGUAGE DataKinds, PolyKinds, KindSignatures, RankNTypes #-}
module Hi where
-- | Failure continuation.
type Failure f r = String -> f r
-- | Success continuation.
type Success a f r = a -> f r
newtype Parser a = Parser {
unParser :: forall f r.
Failure f r
-> Success a f r
-> f r
}
runParser :: Parser a -> Either String a
runParser p = unParser p Left Right
With GHC 7.10 this failed with the quite comprehensible,
Hi.hs:21:20:
A newtype constructor cannot have existential type variables
Parser :: forall a (k :: BOX).
(forall (f :: k -> *) (r :: k).
Failure f r -> Success a f r -> f r)
-> Parser a
In the definition of data constructor ‘Parser’
In the newtype declaration for ‘Parser’
However, with 8.0 the compiler curtly informs you that,
Hi.hs:29:26: error:
• Couldn't match kind ‘GHC.Prim.Any’ with ‘*’
When matching the kind of ‘Either String’
• In the second argument of ‘unParser’, namely ‘left’
In the expression: unParser p left right
In an equation for ‘runParser’:
runParser p
= unParser p left right
where
left !errMsg = Left errMsg
right !x = Right x
As expected, adding a kind signature to Parser
's type variables fixed the issue but the error doesn't help the user realize this nearly as much as it could.