Skip to content

Several Hackage libraries fail to compile due to kind variables not defaulting in HEAD

Originally discovered in a head.hackage CI job here.

After commit 9cc6c193 (Don't default type variables in type families), the following libraries fail to build on head.hackage's CI:

  • inj-base-0.2.0.0
  • lens-5.0.1
  • microlens-0.4.12.0
  • mono-traversable-1.0.15.3

There are likely others, but these are the ones that head.hackage in particular caught. The inj-base failure can be minimized fairly easily:

{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where

data Decision_Wrap
data Decision_Map

type family DecideFn p where
  DecideFn (r -> p) = Decision_Map
  DecideFn p = Decision_Wrap

This compiles on GHC 9.2 and earlier, but fails on HEAD with:

$ ~/Software/ghc-9.3.20211029/bin/ghc Bug.hs
[1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

Bug.hs:9:3: error:
    • Cannot default kind variable ‘t0’
      of kind: GHC.Types.RuntimeRep
      Perhaps enable PolyKinds or add a kind signature
    • In the type family declaration for ‘DecideFn’
  |
9 |   DecideFn (r -> p) = Decision_Map
  |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

Bug.hs:9:3: error:
    • Cannot default kind variable ‘t0’
      of kind: GHC.Types.RuntimeRep
      Perhaps enable PolyKinds or add a kind signature
    • In the type family declaration for ‘DecideFn’
  |
9 |   DecideFn (r -> p) = Decision_Map
  |   ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

I'm unclear if this is expected behavior or not. I certainly hope not, since 9cc6c193 didn't advertise anything in the release notes about this, and this seems like it would break lots of code in the wild. If it is expected, it would be good to document this change and to remove the duplicate error message.

cc @sheaf

To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information