[GHC] #13809: TH-reified data family instances have a paucity of kinds
GHC
ghc-devs at haskell.org
Fri Jun 9 22:54:22 UTC 2017
#13809: TH-reified data family instances have a paucity of kinds
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.0.1
Haskell |
Keywords: TypeFamilies | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Consider this data family (and instances):
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
module Foo where
data family Foo a
data instance Foo ((f :: * -> *) (a :: *))
data instance Foo ((f :: (* -> *) -> *) (a :: (* -> *)))
}}}
These are two data family instances that GHC distinguishes by the kinds of
their type parameters. However, Template Haskell does not give me the same
insight that GHC has, because if I call `Language.Haskell.TH.reify ''Foo`,
I get this:
{{{#!hs
FamilyI
(DataFamilyD
Foo.Foo [ KindedTV a_6989586621679025989 StarT ] (Just StarT))
[ DataInstD
[]
Foo.Foo
[ AppT (VarT f_6989586621679026001) (VarT a_6989586621679026000) ]
Nothing
[]
[]
, DataInstD
[]
Foo.Foo
[ AppT (VarT f_6989586621679026007) (VarT a_6989586621679026006) ]
Nothing
[]
[]
]
}}}
Note that neither `f` nor `a` have a kind signature in either instance!
This makes it completely impossible to tell which is which (aside from the
order, which is brittle). It would make my life a lot easier if TH were to
include kind signatures for each type variable in a data family instance.
I can see two ways to accomplish this:
1. Include a `[TyVarBndr]` field in `DataInstD` and `NewtypeInstD` where
each `TyVarBndr` is a `KindedTV`.
2. Walk over the `Type`s in a `DataInstD`/`NewtypeInstD` and ensure that
every occurrence of a `VarT` is surrounded with `SigT` to indicate its
kind.
While (1) is arguably the cleaner solution, since it makes the kinds easy
to discover, it is a breaking change. Therefore, I'm inclined to implement
option (2) instead.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13809>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list