#1835: Provide information of the instance environment
---------------------------------+------------------------------------------
Reporter: guest | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone: _|_
Component: Template Haskell | Version: 6.8.1
Keywords: | Testcase:
Blockedby: | Difficulty: Unknown
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Changes (by igloo):
* owner: igloo =>
Comment:
Thanks for the patch.
I took a look at it, and it doesn't look like it works how I'd expect for
parameterised types. It also doesn't interact well with other GHC
extensions. For example, this expanded version of your test:
{{{
{-# LANGUAGE TemplateHaskell, FlexibleInstances,
MultiParamTypeClasses, TypeSynonymInstances #-}
module Main where
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
class Eq a => MyClass a where myMeth :: a -> Int
data Foo = Foo deriving Eq
instance MyClass Foo where myMeth = const 1
data Bar = Bar
deriving Eq
type Baz = Bar
instance MyClass Baz
data Quux a = Quux a
deriving Eq
data Quux2 a = Quux2 a
deriving Eq
instance Eq a => MyClass (Quux a)
instance Num a => MyClass (Quux2 a)
class MyClass2 a b
instance MyClass2 Int Bool
main = do
print $(isClassInstance ''Eq (ConT ''Foo) >>= lift)
print $(isClassInstance ''MyClass (ConT ''Foo) >>= lift)
print $ not $(isClassInstance ''Show (ConT ''Foo) >>= lift)
print $(isClassInstance ''MyClass (ConT ''Bar) >>= lift)
print $(isClassInstance ''MyClass (ConT ''Baz) >>= lift)
print $(isClassInstance ''MyClass (AppT (ConT ''Quux) (ConT ''Int)) >>=
lift)
print $(isClassInstance ''MyClass (AppT (ConT ''Quux2) (ConT ''Int))
>>= lift)
print $(isClassInstance ''MyClass2 (ConT ''Int) >>= lift)
print $(isClassInstance ''MyClass2 (ConT ''Bool) >>= lift)
}}}
prints
{{{
True
True
True
False
True
False
False
True
False
}}}
It might be worth taking a step back, and writing a wiki page on exactly
what the behaviour should be.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1835#comment:12>
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