strange overlapping instance error
Dave Herman
dherman at ccs.neu.edu
Wed Jul 11 10:25:38 EDT 2007
I'm a little mystified by an overlapping instance error I'm getting from
GHC (I'm using v6.6.1 in Windows). Here's a simple test case that
demonstrates the type error:
-----
{-# OPTIONS_GHC -fglasgow-exts #-}
module Overlap where
class Needle a
instance Needle String
class Needle b => Haystack a b where
find :: a -> [b]
instance Needle a => Haystack a a where
find a = [a]
instance Haystack a b => Haystack [a] b where
find xs = concatMap find xs
data Tree = Leaf String
| Node [Tree]
instance Haystack Tree String where
find (Leaf s) = find s
find (Node ss) = concatMap find ss
-----
The error is:
overlap.hs:21:18:
Overlapping instances for Haystack String String
arising from use of `find' at overlap.hs:21:18-23
Matching instances:
instance (Needle a) => Haystack a a -- Defined at overlap.hs:11:0
instance (Haystack a b) => Haystack [a] b
-- Defined at overlap.hs:14:0
In the expression: find s
In the definition of `find': find (Leaf s) = find s
In the definition for method `find'
Now, I understand that String is [Char], but since the proposition
(Haystack Char String) is not true, I don't understand why the type
checker is claiming that the second instance declaration matches.
Thanks,
Dave
More information about the Glasgow-haskell-users
mailing list