#5886: TH: Type family instances inside InstanceD are rejected
--------------------------------+-------------------------------------------
 Reporter:  mikhail.vorozhtsov  |          Owner:                  
     Type:  bug                 |         Status:  new             
 Priority:  normal              |      Component:  Template Haskell
  Version:  7.5                 |       Keywords:                  
       Os:  Unknown/Multiple    |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown        |       Testcase:                  
Blockedby:                      |       Blocking:                  
  Related:                      |  
--------------------------------+-------------------------------------------
 The following code is broken by f92591defcb5c4803c301558d51e3f8c9c92a985:
 {{{
 $ cat TH.hs
 {-# LANGUAGE UnicodeSyntax #-}
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}

 module TH where

 import Language.Haskell.TH

 class C α where
   type AT α ∷ ★

 bang ∷ DecsQ
 bang = return [InstanceD [] (AppT (ConT ''C) (ConT ''Int))
                 [TySynInstD ''AT [ConT ''Int] (ConT ''Int)]]
 }}}
 {{{
 $ cat Main.hs
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE TypeFamilies #-}

 import TH

 $(bang)

 main = return ()
 }}}
 {{{
 $ ghc-7.5.20120217 -fforce-recomp -ddump-splices TH.hs Main.hs
 [1 of 2] Compiling TH               ( TH.hs, TH.o )
 [2 of 2] Compiling Main             ( Main.hs, Main.o )
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Loading package pretty-1.1.1.0 ... linking ... done.
 Loading package array-0.3.0.3 ... linking ... done.
 Loading package deepseq-1.2.0.1 ... linking ... done.
 Loading package containers-0.4.2.0 ... linking ... done.
 Loading package template-haskell ... linking ... done.

 Main.hs:6:3:
     Illegal declaration(s) in an instance declaration:
       type instance AT Int = Int
     When splicing a TH declaration:
       instance TH.C GHC.Types.Int
     where type TH.AT GHC.Types.Int = GHC.Types.Int
 }}}
 I attached a patch that fixes the problem (at least for my library).
 Please review.

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