Skip to content

Wrong class instance selection with Data.Kind.Type

If you consider the following code:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleInstances #-}
module Bug where

import GHC.Exts (Constraint)
import Data.Kind

-- | Partial singleton for a kind type.
data SKind k where
  SKiTy :: SKind Type
  SKiCo :: SKind Constraint

instance Show (SKind k) where
  show SKiTy = "*"
  show SKiCo = "Constraint"

class IKind k where
  kind :: SKind k
instance IKind Constraint where
  kind = SKiCo

Then, the main below will compile even though there is no (IKind Type) instance, and it will print "Constraint" two times, instead of an expected "Constraint" then "*":

main :: IO ()
main = do
  print (kind::SKind Constraint)
  print (kind::SKind Type)

And, the main below will print "*" two times, instead of an expected "*" then "Constraint":

instance IKind Type where
  kind = SKiTy

main :: IO ()
main = do
  print (kind::SKind Type)
  print (kind::SKind Constraint)

This can be worked around by replacing Type with a new data type Ty to select the right class instances, using two type families Ty_of_Type and Type_of_Ty, as done in the attached Workaround.hs.

Sorry if this bug has already been fixed in HEAD: I was unable to find neither a bug report similar, nor a Linux x86_64 build of HEAD for me to test.

Trac metadata
Trac field Value
Version 8.0.1
Type Bug
TypeOfFailure OtherFailure
Priority highest
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information