#7477: reifyInstances can't deal with polykinded type families
-----------------------------+----------------------------------------------
Reporter:  goldfire          |          Owner:                                  
      
    Type:  bug               |         Status:  new                             
      
Priority:  normal            |      Component:  Compiler                        
      
 Version:  7.7               |       Keywords:  TemplateHaskell TypeFamilies 
PolyKinds
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple                
      
 Failure:  None/Unknown      |      Blockedby:                                  
      
Blocking:                    |        Related:                                  
      
-----------------------------+----------------------------------------------
 When I run the following code

 {{{
 {-# LANGUAGE DataKinds, KindSignatures, PolyKinds, TypeFamilies,
 TemplateHaskell #-}

 import Language.Haskell.TH

 type family F (a :: k)
 type instance F Int = Bool

 $( do { info <- reifyInstances ''F [ConT ''Int]
       ; reportWarning (pprint info)
       ; return [] })
 }}}

 I get this error:

 {{{
     Wrong number of types (expected 2)
     In the argument of reifyInstances: Main.F GHC.Types.Int
 }}}

 I assumed that TH wanted me to supply the kind parameter, so I tried this:

 {{{
 ...
 $( do { info <- reifyInstances ''F [StarT, ConT ''Int]
 ...
 }}}

 I got this response:

 {{{
     `F' is applied to too many type arguments
     In the argument of reifyInstances: Main.F * GHC.Types.Int
 }}}

 I poked around in the code to see what might be causing it. I found a
 couple of interesting things:

  * {{{reifyInstances}}} uses {{{tyConArity}}} to get the arity of a type
 family. For my {{{F}}}, {{{tyConArity}}} reported 3. So, I wrote some code
 to go through the kind and count only non-superkind arguments. This didn't
 fix the problem, because ...
  * {{{reifyInstances}}} passes control off, through a handful of other
 functions, to {{{matchExpectedFunKind}}}, which works only with
 {{{FunTy}}}, not {{{ForAllTy}}}. So, my {{{F}}}, whose kind is headed by
 {{{ForAllTy}}}, looks like it takes no arguments at all.

 I could try to fix this, but I'm worried about upsetting the apple cart
 here. If a knowledgeable individual could give some pointers about what's
 safe and what's not safe to change in this code, I'm happy to write the
 fix.

 This was all tested on 7.7.20121130.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7477>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to