I have something similar to
> class (Eq a) => Substitutable a where
> match :: a -> a -> Maybe (Substitution a)
> applySubst :: Substitution a -> a -> a
and two Types Type1, Type2, both of which are instances of class
Substitutable. In some places there is a sigma :: Substitution Type1
(or a phi :: Substitution Type2) to be applied to list :: [(Type1,
Type2)].
Now, something like
> map (\(x, y) -> (applySubst sigma x, y)) list
or
> [(applySubst sigma x, y) | (x,y) <- list]
is used (accordingly for phi). What I would prefer
> map (applySubst sigma) list
or
> map (applySubst phi) list
but defining
> instance Substitutable a => Substitutable (a,b) where
> applySubst sigma (x,y) = (applySubst sigma x, y)
> instance Substitutable b => Substitutable (a,b) where
> applySubst phi (x,y) = (x, applySubst phi y)
obviously has an overlapping instance (which will never occur).
I would greatly appreciate any suggestions on how handle this
situation.
Marko
--
Marko Schütz [EMAIL PROTECTED]
http://www.ki.informatik.uni-frankfurt.de/~marko/