[GHC] #9768: reify returns only first instance of class

GHC ghc-devs at haskell.org
Tue Nov 4 14:23:08 UTC 2014


#9768: reify returns only first instance of class
-------------------------------------+-------------------------------------
       Reporter:  qnikst             |                   Owner:
           Type:  bug                |                  Status:  new
       Priority:  normal             |               Milestone:
      Component:  Compiler           |                 Version:  7.8.3
       Keywords:                     |        Operating System:
   Architecture:  Unknown/Multiple   |  Unknown/Multiple
     Difficulty:  Unknown            |         Type of failure:
     Blocked By:                     |  None/Unknown
Related Tickets:                     |               Test Case:
                                     |  https://gist.github.com/qnikst/b93e7154e78bcc159be2
                                     |                Blocking:
                                     |  Differential Revisions:
-------------------------------------+-------------------------------------
 In ghc-7.8 reify returns only first data type that have an instance, here
 is a code:

 Test.hs

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 module Test where

 import Language.Haskell.TH

 class C a

 inner :: ExpQ
 inner = do
   ClassI _ instances <- reify ''C
   let sh = show instances
   [| sh |]

 def :: String -> DecsQ
 def x =
   let dn = mkName x
   in do dt <- dataD (cxt []) dn [] [] []
         i <- instanceD (cxt []) (appT (conT ''C) (conT dn)) [] -- [d|
 instance C $(cn) |]
         return [dt,i]

 test :: ExpQ
 test = [| print $inner |]
 }}}

 test.hs
 {{{
 {-# LANGUAGE TemplateHaskell #-}

 import Test

 def "A"
 def "B"

 main = $(test)
 }}}

 running test returns:

 "[InstanceD [] (AppT (ConT Test.C) (ConT Main.A)) []]"


 under 7.6 test returns:

 "[InstanceD [] (AppT (ConT Test.C) (ContT Main.B) [], InstanceD [] (AppT
 (ConT Test.C) (ConT Main.A) []]"

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


More information about the ghc-tickets mailing list