I feel now that the overlapping instances are, generally, all right
in Haskell.
Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]>
had set certain example to show their inconsistensy.
In my last letter I admitted that this example presented a problem.
But now, I think there is no problem.
Let us recall it.
K> f :: Eq a => [a] -> [a]
K> f (x1:x2:xs) = if Just x1 == Just x2 then xs else []
K> [..]
K> It's not enough for the compiler to just remember after compiling
K> f that it needs an explicit dictionary of Eq (Maybe a) passed, and
K> generate different calls to f than to other functions of the same type,
K> because a function like
K> g :: Eq a => ([a] -> [a]) -> [[a]] -> Int
K> does not know what kind of f will receive (the one that depends
K> on Eq (Maybe a), or possibly Eq (a,Bool) etc.) - it is determined
K> at runtime.
Jeffrey R. Lewis <[EMAIL PROTECTED]> wrote on 24 Feb 2000
> The higher-order case isn't any more interesting than the
> first-order case. The designers of the type class system were clever
> enough to avoid this snafu ;-) Instance resolution is part of static
> type inference, it is not determined at runtime.
> In particular, it is not the responsibility of `g' to pass
> dictionaries to any parameter `f' - this would be handled at the
> point where `g' is applied to `f'. Parameters, whether higher-order
> or not, are always monomorphic, and non-overloaded. Only
> `let'/`where' bound idents, or top-level bound idents can be
> overloaded. If we want to think in terms of the dictionary
> translation, in the translation of `g f', `f' would be partially
> applied to its dictionaries, and then passed to `g'.
>
> g f --> \d -> g (f d)
> (assuming that `g' itself wasn't overloaded, and that `f' was only
> overloaded on one thing).
>
> As for your later question about module `E' - it would be helpful
> if you'd provide the exact module that you used.
This sounds rather dim to me.
Here is certain concrete example, after the same idea.
Maybe, you explain how the existing implementations would generate
and pass the dictionaries?
--------------------------------------------------------------------
module F (f)
where
f :: (Eq a, Eq (Maybe a)) => a -> Bool
f x = (Just x)==(Just x)
instance Eq (Maybe Bool) -- overlaps with standard
where -- Eq instance for Maybe a
Nothing == Nothing = True
Just x == Just y = x==(not y) -- contrived example
_ == _ = False
-- example: (Just True )==(Just True ) = False
-- (Just True )==(Just False) = True
------------
module G (g)
where
g :: Eq a => (a -> Bool) -> [a] -> [Bool]
g h xs = map h xs
------------
module Main
where
import F (f)
import G (g)
e = g f [True] :: [Bool]
main = putStr $ shows e "\n"
--------------------------------------------------------------------
And suppose the compiler do *not* inline the functions into the
interface modules - bring the compiler into such a mode.
Now, e has to evaluate as follows:
map f [True] = [f True] = [(Just True)==(Just True)] = [?]
If the overlapping instances really work, then the result should be
[False] - because the most special instance dictionary for
Eq (Maybe a) is passed to f is expression map f [True].
And this example is contrived. It is set deliberately so that the
instances lead to different results - to test the existing
implementations.
In the regular practice, I believe, a sensible programing is to set
the overlapping instances so that the difference would be only in
the way of computation, not in the result.
Now, testing the system ghc-current-cvs-Feb-14-2000,
with -fglasgow-exts -optC-fallow-overlapping-instances,
indeed, produces e = [False].
And commenting out the instance for Eq (Maybe Bool) returns it to
[True].
Now, how it resolves statically which dictionary to pass to these
call of f in Main.e ? What is the origin of these dictionaries
?
The problem was set as follows. Compiling Main.e, the compiler
sees only the types of g, f, it does not see the fact that (==)
will be applied to (Just True) ... at the run-time.
Hence, is it likely to pass to f the generic dictionary from
Eq a => Eq (Maybe a)
?
If so, this would spoil the overlapping instance business.
But probably, we guess, how it is done - very naturally.
To compile E and resolve the instance overlap, one does not need
looking into the implementation of F,G.
It only needs to match the types of the result and the
argument types in the functions f, g, e.
As to e, the implementation is also visible.
When compiling Main.e,
about f, it is visible f :: (Eq a, Eq (Maybe a)) => a -> Bool
About g,
it is visible that its first argument (h) has the type
Eq a => a -> Bool
and the second argument has the type [a]
- where `a' is the parameter from the first argument type.
About e, the compiler sees the body of e, it sees g f [True].
Hence the type of `f' occurrence in e has to agree to the type of
the first argument of g:
Eq a => a -> Bool.
The type of the f occurrence in e has also to agree to the type
of [True]
- the compiler recalls the restriction from g:
`where `a' is the parameter from the first argument type'.
Hence, in e, a = Bool.
Therefore, the type of f occurence in e has to be Bool -> Bool.
But then, it is statically visible, that both the dictionaries,
from Eq a => Eq (Maybe a)
and from Eq (Maybe Bool)
fit to be passed to the f occurrence in e.
The compiler chooses the second as the most special.
Right? Do the existing implementations follow this?
This example differs from the one by Marcin, and it is slightly
simpler.
But evidently, the method applies to Marcin's example too.
------------------
Sergey Mechveliani
[EMAIL PROTECTED]