On Mon, 28 Feb 2000, S.D.Mechveliani wrote:

> If we want the recent implementations to compile this as needed, we
> have to write
>   g :: (Eq a, Eq (Maybe a)) => (a -> Bool) -> [a] -> [Bool]
>               ------------
>   g h xs@(x:_) = (Just x == Just x) : map h xs
> 
> - "because this  g  uses  Eq (Maybe a)".

It can't be. First, with polymorphic recursion the function uses an
unbounded number of instances, and the context must be finite.

Second, I don't want my programs to be big and slow only because
somebody wanted an extension which caused the compiler to pass 10
instances instead of 2 to my functions (that don't use the extension
of overlapping instances).

Third, it does not work well with local universal quantification:
    data A = A (forall a. Eq a => [a] -> a)
I want to be able to say "W f" where f happens to use the Eq (Maybe a)
instance.

Fourth, it does not work well with local existential quantification:
    data E = forall a. Eq a => E a (a -> [a])
I want to be able to say "case e of E x f -> Just x == listToMaybe (f x)"
without the compiler complaining that it can't safely generate the
equality on Maybe because it is not sure whether the hidden type has
redefined equality on its Maybe or not.

> With omitting  Eq (Maybe a),  some implementations even report an
> error - when compiling  E.

Only when there is an instance like Eq (Maybe String) in scope.

> Finally, I continue suggesting what I call *deduced context*.

It has been discussed. It could be convenient. Possibly not only in
contexts, but also in parts of types.

However it would not prevent the poor compiler from being required to
pass all these dictionaries at runtime, even if it makes a little sense
because I will certainly not redefine equality on (String,Int) etc.

> > The question remains whether to prohibit them even when the relevant
> > instances are not visible.
> 
> Looks like the compiler has to care only of the visible (in scope)
> relevant instances. Why should it care for others?

Because the function might be called from another module, on a type
which has overlapping instances defined, and the semantics would
better not depend on whether I imported a module or not, or whether
functions are inlined.

> > one must be careful to either import enough instances or provide
> > explicit type signatures in all relevant places 
> 
> Most natural style. Why not?

It's not obvious which modules are needed. I might not need any values,
types or classes from them, only instances, and they are imported
and exported implicitly (which is IMHO good, at least by default).

> > - failure to do so will produce incorrect result without warning, 
> 
> No: the same result, but maybe, with greatly different cost.

Only if you use overlapping instances only for cases that differ in
cost, not in semantics.

> > [..] A habit of defining instances in the module containing
> > either the class definition or the type definition reduces the
> > possibility of conflict to some two modules which would have to be
> > [..]
> 
> Happily, it is only a habit!
> I wonder how could I develop my CA project if this was the language 
> requirement. This should have most stuckkily stuck it.

Strange.

> In brief, is has to support the overlapping instances like for the
> class  Cast a b.  Defining its instances (together with certain
> compiler pragma) gives a nice tool for the user to set the implicit
> domain casting.

I believe that C++ allows only one user defined type conversion at
a time because the general problem of finding a path of conversions
is undecidable. Cast a b with instances like
    instance (Cast a b, Cast b c) => Cast a c where cast = cast . cast
is even more general and I'm sure that the whole thing gets undecidable.

Moreover, it is very easily ambiguous. Even if various possibilities
would yield the same result, the compiler can't prove it. IMHO
designing a set of complex rules of choosing the best way among several
valid ways is a path to nowhere (and simple rules will not do). It's
a mess, especially if added to such poweful system as Haskell's
classes. It's an effective method of making users furious because the
compiler is not choosing the way they want. It's a pain for compiler
writers: expect various compilers behaving differently in subtle cases.
No, Haskell is not worth it.

Remember: today about the only place in Haskell where the compiler
resolves an ambiguity itself without reporting an error, where it
chooses an interpretation while another interpretation would be valid
too, is defaulting numeric classes. And GHC -Wall warns when they fire.
The less such cases, the better.

> Such a casting is of great importance, at least, in computer algebra.
> It is a pity that, due to the overlaps lack, my recent CA program
> is not able to support this cast.

I'm afraid that such casting is incompatible with Haskell, or even
impossible to be sanely expressed in any language.

-- 
 __("<    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-

Reply via email to