Wed, 16 Feb 2000 15:45:07 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze:
> I fear, I am loosing the thread. The discussion was on the
> overlapping instances. And this latter question is maybe, on giving
> a polymorphic function to another function as the argument. I am
> not an implementor and doubt about `dictionaries', still could we
> put it more concretely?
f:: Eq a => [a] -> [a]
f (x1:x2:xs) = if Just x1 == Just x2 then xs else []
(Sorry, the example is artificial because I have chosen such types.)
How does a compiler implement f? A common technique is to associate
dictionaries (records) of methods with classes. It gets equivalent
to this:
-- Translation of class Eq:
data Eq a = Eq {(==), (/=) :: a -> a -> Bool}
-- Translation of instance Eq Int:
eqInt:: Eq Int
eqInt = Eq {primEqInt, (not .) . primEqInt}
-- Translation of instance Eq a => Eq (Maybe a):
eqMaybe:: Eq a -> Eq (Maybe a)
eqMaybe eqOnArg = Eq {eq, (not .) . eq}
where
eq Nothing Nothing = True
eq (Just a) (Just b) = (==) eqOnArg a b
eq _ _ = False
-- Translation of f :: Eq a => [a] -> [a]:
f:: Eq a -> [a] -> [a]
f eq (x1:x2:xs) = if (==) (eqMaybe eq) x1 x2 then xs else []
That is, f receives a dictionary of Eq methods on the type a, as
specified in its type. It builds a dictionary of Eq methods on the
type Maybe a itself, but the fact that it uses instance Eq (Maybe a)
is not visible outside.
Now, what happens with overlapping instances, when the user defines:
instance Eq (Maybe String) where
Nothing == Nothing = True
Just a == Just b = length a == length b
_ == _ = False
and uses f ["foo","bar","baz"]? f has the implementation like above
and has only one (polymorphic) implementation, so it produces the
dictionary of Eq (Maybe String) basing on the general eqMaybe and
equality on strings (synthesized from the equality on characters and
lists), ignoring the more specific instance.
If the compiler specialized f by generating separate implementation of
fOnString :: [String] -> [String]
like in C++, it could have a chance of seeing that it requires special
treatment of Maybe instance. But in general it can't always specialize:
polymorphic recursion may generate unbounded number of specializations,
and such specialization is very hard in separate compilation.
It's not enough for the compiler to just remember after compiling
f that it needs an explicit dictionary of Eq (Maybe a) passed, and
generate different calls to f than to other functions of the same type,
because a function like
g :: Eq a => ([a] -> [a]) -> [[a]] -> Int
does not know what kind of f will receive (the one that depends
on Eq (Maybe a), or possibly Eq (a,Bool) etc.) - it is determined
at runtime.
ghc-4.06 in fact does not see the Eq (Maybe String) instance in the
above case. It sees it when the type signature is changed to
f :: Eq (Maybe a) => [a] -> [a]
which is not legal in Haskell 98 at all, or when the type signature
is omitted (when it's probably inferred to Eq (Maybe a) => ...
instead of Eq a => ... as in standard Haskell - context reduction
must be deferred, one cannot reduce Eq (Maybe a) to Eq a as normally).
But even if the type of f is Eq (Maybe a) => ..., when f is used
inside a function of type Eq a => ... on the same type a, that
outside function generates the dictionary of Maybe a and uses the
only generically applicable method: generic instance Eq (Maybe a),
so f does not see instance Eq (Maybe String).
I do not blame ghc for that. IMHO overlapping instances together
with the rest of Haskell are impossible to be safely and effectively
implemented.
Unless one accepts that subtle differences in contexts, ones
depending on the implementation rather than the interface, change
the meaning. And that definition like "g :: some signature; g = f"
can cause g to be defined on exactly the same types as f, but with
a different meaning. And that the same polymorphic function used on
the same type has different meanings in various places.
--
__("< Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
\__/ GCS/M d- s+:-- a22 C+++$ UL++>++++$ P+++ L++>++++$ E-
^^ W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK 5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-