Type synonyms are not expanded in the data type declaration return kind
I was playing around with the cool new -XTypeInType
stuff when I encountered the following issue:
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE GADTs #-}
module TypeInTypeBug where
import qualified Data.Kind
-- This works, using Data.Kind.Type as return kind
--------------vvvvvvvvvvvvvv
data Works :: Data.Kind.Type where
WorksConstr :: Works
type Set = Data.Kind.Type
-- This doesn't work, using a type synonym for Data.Kind.Type as return kind
---------------vvv
data Doesnt :: Set where
DoesntConstr :: Doesnt
TypeInTypeBug.hs:17:1: error:
• Kind signature on data type declaration has non-* return kind Set
• In the data declaration for ‘Doesnt’
I suppose type synonyms should be expanded in the return kind of a data type declaration before checking it is *
.
I also think the error message is not totally correct, take the following valid data declaration:
data Foo :: Bool -> Data.Kind.Type where
Tru :: Foo True
Fal :: Foo False
The return kind of the data declaration is actually Bool -> Data.Kind.Type
(or Bool -> *
), which is not *
. I assume the error message is talking about the return kind (*
) of the return kind (Bool -> *
)
Trac metadata
Trac field | Value |
---|---|
Version | 7.11 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler (Type checker) |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | goldfire |
Operating system | |
Architecture |