[GHC] #13809: TH-reified type familly and data family instances have a paucity of kinds

GHC ghc-devs at haskell.org
Fri Jun 9 23:15:22 UTC 2017


#13809: TH-reified type familly and data family instances have a paucity of kinds
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Template Haskell  |              Version:  8.0.1
      Resolution:                    |             Keywords:  TypeFamilies
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #8953             |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * related:   => #8953


Comment:

 Ugh, and it affects class instances too:

 {{{#!hs
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE TypeFamilies #-}
 module Foo where

 class Foo a
 instance {-# OVERLAPPING #-} Foo ((f :: *        -> *) (a ::       *))
 instance {-# OVERLAPPING #-} Foo ((f :: (* -> *) -> *) (a :: (* -> *)))
 }}}
 {{{#!hs
 ClassI
   (ClassD [] Foo.Foo [ KindedTV a_6989586621679013875 StarT ] [] [])
   [ InstanceD
       (Just Overlapping)
       []
       (AppT
          (ConT Foo.Foo)
          (AppT (VarT f_6989586621679013885) (VarT a_6989586621679013886)))
       []
   , InstanceD
       (Just Overlapping)
       []
       (AppT
          (ConT Foo.Foo)
          (AppT (VarT f_6989586621679013890) (VarT a_6989586621679013891)))
       []
   ]
 }}}

 Richard went part of the way in fixing these sorts of issues in #8953, but
 he avoided going too far in annotating every variable with a kind.
 Personally, I think he didn't go too far enough :)

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13809#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list