#4135: Can't Quote Instance Associated Types in Template Haskell
---------------------------------+------------------------------------------
    Reporter:  Ashley Yakeley    |        Owner:                           
        Type:  bug               |       Status:  new                      
    Priority:  normal            |    Milestone:                           
   Component:  Template Haskell  |      Version:  6.12.1                   
    Keywords:                    |   Difficulty:                           
          Os:  Linux             |     Testcase:                           
Architecture:  x86_64 (amd64)    |      Failure:  GHC rejects valid program
---------------------------------+------------------------------------------

Comment(by simonpj):

 Actually the email cited has a different problem
 {{{
 {-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, TypeFamilies,
              FlexibleInstances, OverlappingInstances #-}

 module Sample where

 import Control.Monad
 import Language.Haskell.TH

 class Foo a where
     type FooType a

 createInstance' :: Q Type -> Q Dec
 createInstance' t = liftM head [d|
     instance Foo $t where
     type FooType $t = String |]
 }}}
 This fails with a similar error:
 {{{
 Sample.lhs:22:10:
     Type indexes must match class instance head
     Found `t_aMn' but expected `t_aMl'
 }}}
 Here it's plain that we can't really do full type-checking of the quoted
 instance until `createInstance'` is applied, so that we can run the splice
 `$t`.  Somehow TH needs to be less picky about the consistency checks on
 types when typechecking quotes.

 The earlier example, though, should be fine. I'll look into it.

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4135#comment:2>
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