I discovered this while implementing instances of HasResponse for RespondAs. I’ve boiled it down to the following minimal example, which has to be split across 2 files, one of which has PolyKinds enabled and the other does not (the only other extensions enabled at the package level are ScopedTypeVariables and FlexibleInstances):
-- X.hs
{-# LANGUAGE PolyKinds #-}
module X where
data X p a
-- HasTypeRep.hs
module HasTypeRep where
import Data.Typeable
import X
class HasTypeRep a where
getTypeRep :: Proxy a -> TypeRep
instance {-# OVERLAPPABLE #-} (Typeable a) => HasTypeRep a where
getTypeRep = typeRep
instance {-# OVERLAPPING #-} (HasTypeRep a) => HasTypeRep (X p a) where
getTypeRep _ = getTypeRep (Proxy :: Proxy a)
I know, careless overuse of OVERLAPPING is an easy way to weirdness, but anyway… Let’s load this in a repl, with DataKinds enabled (I’ve tested this with GHC 9.8.4):
-- works as intended
ghci> getTypeRep $ (Proxy :: Proxy (X () Int))
Int
ghci> getTypeRep $ (Proxy :: Proxy (X Char Int))
Int
-- until..
ghci> getTypeRep $ (Proxy :: Proxy (X 'True Int))
X Bool * 'True Int
ghci> getTypeRep $ (Proxy :: Proxy (X '() Int))
X () * '() Int
ghci> getTypeRep $ (Proxy :: Proxy (X '[Char] Int))
X [*] * (': * Char ('[] *)) Int
It seems that when the p type variable of X has kind Type, then GHC uses the second instance; but when it has any other kind, the first.
This can be easily solved by enabling PolyKinds in the HasTypeRep module, but I thought this was worth noting.