#2853: Defaulting not used enough with type families
-----------------------------+----------------------------------------------
Reporter: guest | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.10.1 | Severity: normal
Keywords: | Testcase:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
-----------------------------+----------------------------------------------
Consider this module
{{{
{-# LANGUAGE TypeFamilies, ExtendedDefaultRules #-}
module Bug3 where
class C t where
type T t
instance C Integer where
type T Integer = Integer
data (C t, Num t) => D t = D (T t)
instance Show (D a) where show _ = ""
}}}
Now let's try to ask for the type of (D 5)
{{{
*Bug3> :t D 5
D 5 :: (Num (T t), C t, Num t) => D t
}}}
That's great. Now if we try to show this value it should have type
{{{
(Num (T t), C t, Num t) => String
}}}
And now the defaulting mechanism should set t to Integer, which would
resolve the rest of the context. But instead we get this:
{{{
*Bug3> :t show (D 5)
<interactive>:1:8:
No instance for (Num (T t))
arising from the literal `5' at <interactive>:1:8
Possible fix: add an instance declaration for (Num (T t))
In the first argument of `D', namely `5'
In the first argument of `show', namely `(D 5)'
In the expression: show (D 5)
}}}
It looks like the defaulting never got used.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2853>
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