using FlexibleInstances and OverlappingInstances

Hello, In a module I am writing, I would like to use FlexibleInstances and OverlappingInstances. But I get errors, so I am trying to reproduce the problems on a smaller program: -------------------------------------------- {-# LANGUAGE FlexibleInstances, OverlappingInstances #-} data Foo = Foo Int deriving ( Show ) instance Show [Foo] where show [] = "[0]" show l = map show l main = do let l = [ Foo 1, Foo 2 ] print l -------------------------------------------- The first error I obtain is: -------------------------------------------- test_overlappinginstances.hs:7:19: Couldn't match expected type `Char' with actual type `[Char]' Expected type: a0 -> Char Actual type: a0 -> String In the first argument of `map', namely `show' In the expression: map show l -------------------------------------------- Where does this "Char" come from? How to solve this problem? The second error is: -------------------------------------------- test_overlappinginstances.hs:11:5: Overlapping instances for Show [Foo] arising from a use of `print' Matching instances: instance Show a => Show [a] -- Defined in GHC.Show instance [overlap ok] Show [Foo] -- Defined at test_overlappinginstances.hs:5:10-19 -------------------------------------------- The overlap is ok ("overlap ok" does not appear if not using the pragma OverlappingInstances), so it should work? Thanks in advance, TP

On Sat, Apr 7, 2012 at 12:08 PM, TP
Hello,
In a module I am writing, I would like to use FlexibleInstances and OverlappingInstances. But I get errors, so I am trying to reproduce the problems on a smaller program:
Is your actual issue with Showing a list? If so, you might be better off using the 'showList' member of the 'Show' typeclass: instance Show Foo where show x = ... showList xs = ... Then your 'showList' method will be called when 'show' is called on a list of 'Foo' values. The first error is because 'map show l' is the wrong type - mapping show over a list will give you a list of strings, but 'show' must return a string. I think you could use 'concatMap' here. Other than that the only advice I can give is that I try my hardest to avoid OverlappingInstances. Antoine Antoine
-------------------------------------------- {-# LANGUAGE FlexibleInstances, OverlappingInstances #-}
data Foo = Foo Int deriving ( Show )
instance Show [Foo] where show [] = "[0]" show l = map show l
main = do let l = [ Foo 1, Foo 2 ] print l --------------------------------------------
The first error I obtain is: -------------------------------------------- test_overlappinginstances.hs:7:19: Couldn't match expected type `Char' with actual type `[Char]' Expected type: a0 -> Char Actual type: a0 -> String In the first argument of `map', namely `show' In the expression: map show l --------------------------------------------
Where does this "Char" come from? How to solve this problem?
The second error is: -------------------------------------------- test_overlappinginstances.hs:11:5: Overlapping instances for Show [Foo] arising from a use of `print' Matching instances: instance Show a => Show [a] -- Defined in GHC.Show instance [overlap ok] Show [Foo] -- Defined at test_overlappinginstances.hs:5:10-19 --------------------------------------------
The overlap is ok ("overlap ok" does not appear if not using the pragma OverlappingInstances), so it should work?
Thanks in advance,
TP
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Saturday 07 April 2012 14:22:15 you wrote:
Is your actual issue with Showing a list? If so, you might be better off using the 'showList' member of the 'Show' typeclass:
instance Show Foo where show x = ... showList xs = ...
Then your 'showList' method will be called when 'show' is called on a list of 'Foo' values.
Yes, my problem is to show a list. Thanks a lot. Your solution should work in my more complicated module. I have modified the simple program of my post to make it work with showList as you advised: ---------------------------- data Foo = Foo Int instance Show Foo where show (Foo i) = show i -- Implementation of showList found at: -- http://www.haskell.org/pipermail/haskell-cafe/2010-May/077818.html -- showList [] = showString "[]" -- showList (x:xs) = showChar '[' . shows x . showl xs -- where showl [] = showChar ']' -- showl (x:xs) = showChar ',' . shows x . showl xs -- So with the inspiration from above, I can create my implementation -- in the accumulator style: -- http://www.willamette.edu/~fruehr/haskell/evolution.html -- Not a lot of information on Show instance. "Haskell, the Craft of -- functional programming" quotes: -- http://www.haskell.org/tutorial/stdclasses.html#sect8.3 -- Not a lot of information at: -- http://book.realworldhaskell.org/read/using-typeclasses.html#id608052 showList [] = shows "Empty list" showList (x:xs) = showChar '<' . shows x . showl xs where showl [] = showChar '>' showl (x:xs) = showChar ';' . shows x . showl xs main = do print [ Foo 1, Foo 2] print ([] :: [Foo]) ----------------------------
The first error is because 'map show l' is the wrong type - mapping show over a list will give you a list of strings, but 'show' must return a string. I think you could use 'concatMap' here.
Thanks. The first error was so stupid... Perhaps I was a little disturbed by overlapping instances.
Other than that the only advice I can give is that I try my hardest to avoid OverlappingInstances.
I have found more information about overlapping instances at: http://book.realworldhaskell.org/read/using-typeclasses.html#id608052 but it does not seem to work well; or it is rather tricky: I have been unable to make my initial post example work with overlapping instances. However, I don't see why it could not work. Thanks TP
participants (2)
-
Antoine Latter
-
TP