[Haskell-cafe] using FlexibleInstances and OverlappingInstances
Antoine Latter
aslatter at gmail.com
Sat Apr 7 21:22:15 CEST 2012
On Sat, Apr 7, 2012 at 12:08 PM, TP <paratribulations at free.fr> wrote:
> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list