#5452: reify yields incorrect TupleT at higher-kinds
---------------------------------+------------------------------------------
    Reporter:  nicolas.frisby    |       Owner:                           
        Type:  bug               |      Status:  new                      
    Priority:  normal            |   Component:  Template Haskell         
     Version:  7.2.1             |    Keywords:                           
    Testcase:                    |   Blockedby:                           
          Os:  Unknown/Multiple  |    Blocking:                           
Architecture:  Unknown/Multiple  |     Failure:  GHC rejects valid program
---------------------------------+------------------------------------------
 Line 1175 of changeset:0237ed6762fc86d0eb5db02a8e02ebe35d8d7272 introduces
 a bug where reify yields an application of `TupleT` where its argument is
 too small when the type being reified is of a higher-kind than `*`.

 For example, in the `Applicative` instance for `((,) a)`; the `(,)` gets
 reified as `TupleT 1` instead of `TupleT 2`.

 Here's some code that duplicates its `C` instance to be a `D` instance.

 {{{
 {-# LANGUAGE TemplateHaskell, KindSignatures, FlexibleInstances #-}

 module ReifyTupleBug where

 import Language.Haskell.TH

 class C (f :: * -> *)
 class D (f :: * -> *)

 instance C ((,) Int)

 reify ''C >>= \(ClassI _ [i]) ->
   return [InstanceD (ci_cxt i) (foldl AppT (ConT ''D) (ci_tys i)) []]
 }}}

 It results in a kind mis-match:

 {{{
 ReifyTupleBug.hs:13:1:
     Kind mis-match
     The first argument of `D' should have kind `* -> *',
     but `Int' has kind `*'
     In the instance declaration for `D Int'
 Failed, modules loaded: none.}}}

 I'm not sure how `reify_tc_app` should be adjusted; perhaps it needs to
 know the kind at which it is operating and then increment `n_tys` based on
 the number of arrows?

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

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to