Skip to content

HEAD regression: GHC no longer accepts fixity declaration in class

(Originally observed in a head.hackage issue: head.hackage#88 (closed))

GHC HEAD (at commit eb1a6ab1) rejects the following program, which earlier versions of GHC accept:

{-# LANGUAGE TypeFamilies #-}
module Bug where

class POrd a where
  type a >= b
  infix 4 >=
$ ghc-9.6.2 Bug.hs
[1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

$ ghc-9.9.20230716 Bug.hs
[1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

Bug.hs:6:11: error: [GHC-54721]
    ‘>=’ is not a (visible) method of class ‘POrd’
  |
6 |   infix 4 >=
  |           ^^

Note that:

  • It is important that >= also be the name of another identifier already in scope. If I rename >= to, say, >==, then the error disappears.
  • It is also important that >= be an associated type family. If I change >= to an ordinary class method, then the error disappears.
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information