
Cannot deduce (Show x) from context (Show (x, y)). Cannot deduce (Show y) from context (Show (x, y)). Um... seriously? From Prelude, we have Show x, Show y => Show (x, y) So clearly it works in the forward direction. But apparently not in the reverse direction. Is this a bug or a feature? (I.e., is there some obscure possibility I haven't thought of which means that doing the reverse inference would be incorrect?)

And I can declare an instance for (x, y) which does NOT implies (Show x):
instance Show (x, y) where
show _ = "I'm tuple! Hooray!"
Andrew Coppin
Cannot deduce (Show x) from context (Show (x, y)). Cannot deduce (Show y) from context (Show (x, y)).
Um... seriously?
From Prelude, we have
Show x, Show y => Show (x, y)
So clearly it works in the forward direction. But apparently not in the reverse direction.
Is this a bug or a feature? (I.e., is there some obscure possibility I haven't thought of which means that doing the reverse inference would be incorrect?)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 19/05/2011 10:11 PM, Artyom Kazak wrote:
And I can declare an instance for (x, y) which does NOT implies (Show x):
instance Show (x, y) where show _ = "I'm tuple! Hooray!"
Ah. So it's a feature. Fortunately I refactored the program where this came up, so it's no longer an issue. I just wanted to see whether or not it was a bug. PS. Wouldn't such an instance require FlexibleContexts or something?

If you have nested type, then it usually makes sense to have Show defined
for the inside types, too, but it's not a requirement. Technically, only
when you call 'show' for something in the data type you are defining Show
for, *then* you need a Show instance defined for that inside-type.
On Fri, May 20, 2011 at 12:15 AM, Andrew Coppin wrote: On 19/05/2011 10:11 PM, Artyom Kazak wrote: And I can declare an instance for (x, y) which does NOT implies (Show x): instance Show (x, y) where
show _ = "I'm tuple! Hooray!" Ah. So it's a feature. Fortunately I refactored the program where this came up, so it's no longer
an issue. I just wanted to see whether or not it was a bug. PS. Wouldn't such an instance require FlexibleContexts or something? _______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe --
Markus Läll

On Thursday 19 May 2011 23:15:06, Andrew Coppin wrote:
On 19/05/2011 10:11 PM, Artyom Kazak wrote:
And I can declare an instance for (x, y) which does NOT implies (Show x):
instance Show (x, y) where show _ = "I'm tuple! Hooray!"
Ah. So it's a feature.
Fortunately I refactored the program where this came up, so it's no longer an issue. I just wanted to see whether or not it was a bug.
PS. Wouldn't such an instance require FlexibleContexts or something?
No, the instance head is a type constructor applied to two distinct type variables, it's a perfectly valid H98 instance declaration. It won't be accepted though, because there is already instance (Show x, Show y) => Show (x,y) where ... I think basically the only way to make GHC accept the above instance involves NoImplicitPrelude (but I may be wrong).

Think of it this way:
-- Here is some data representing the typeclass 'Show'
data ShowDict a = ShowD (a -> String)
show :: ShowDict a -> a -> String
show (ShowD f) a = f a
-- Here's a sample implementation for Strings
showString :: ShowDict String
showString = ShowD (\s -> "\"" ++ escape s ++ "\"") where
escape = concatMap escapeChar
escapeChar '\\' = "\\\\"
escapeChar '"' = "\\\""
escapeChar c = [c]
-- Here's an implementation for pairs that uses the implementation for each
piece of the pair
showPair :: ShowDict a -> ShowDict b -> ShowDict (a,b)
showPair (ShowD sa) (ShowD sb) = ShowD (\(a,b) -> "(" ++ sa a ++ ", " ++ sb
b ++ ")")
-- Here is what you are asking for
implementMe :: ShowDict (a,b) -> ShowDict a
implementMe = ????
On Thu, May 19, 2011 at 2:08 PM, Andrew Coppin
Cannot deduce (Show x) from context (Show (x, y)). Cannot deduce (Show y) from context (Show (x, y)).
Um... seriously?
From Prelude, we have
Show x, Show y => Show (x, y)
So clearly it works in the forward direction. But apparently not in the reverse direction.
Is this a bug or a feature? (I.e., is there some obscure possibility I haven't thought of which means that doing the reverse inference would be incorrect?)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Andrew Coppin
-
Artyom Kazak
-
Daniel Fischer
-
Markus Läll
-
Ryan Ingram