[GHC] #8625: GHCi does not support some TH elements, while those elemenst are working in hs files

GHC ghc-devs at haskell.org
Mon Dec 23 11:31:31 UTC 2013


#8625: GHCi does not support some TH elements, while those elemenst are working in
hs files
------------------------------------+-------------------------------------
       Reporter:  danilo2           |             Owner:
           Type:  bug               |            Status:  new
       Priority:  normal            |         Milestone:
      Component:  GHCi              |           Version:  7.7
       Keywords:                    |  Operating System:  Unknown/Multiple
   Architecture:  Unknown/Multiple  |   Type of failure:  None/Unknown
     Difficulty:  Unknown           |         Test Case:
     Blocked By:                    |          Blocking:
Related Tickets:                    |
------------------------------------+-------------------------------------
 Hello. Below is a code, which works when using runhaskell, but does not
 work in GHCi.

 In GHCi we get following error:
 runQ [d| instance ( y ~ (t->t) ) => Member Vector y where member v = test
 |]
 <interactive>:19:6:
     Exotic predicate type not (yet) handled by Template Haskell
       y ~ (t -> t)

 code:

 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE TemplateHaskell #-}
 module Main where

 import Language.Haskell.TH

 class a ~ b => HEq a b

 test :: a -> a
 test x = x

 data Vector
 class Member a b where member :: a -> b

 main :: IO ()
 main = print =<< runQ [d| instance y ~ (t->t) => Member Vector y where
 member v = test  |]

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


More information about the ghc-tickets mailing list