Thu, 10 Feb 2000 23:00:08 +0300 (MSK), S.D.Mechveliani <[EMAIL PROTECTED]> pisze:

> > Generally it does not fit into my mental model of a Haskell class.
> > How could it be that adding an instance *constrains* what else we
> > can do with a type (define an instance of another class)?
> 
> In what way it constrains what else we can do with a type?

I think I was a bit mistaken about how ghc handles overlapped
instances. However in the following case there is an ambiguity that
I don't know how to resolve - overlapping instances don't solve what
they seemed to claim to solve:

class        A a where ...
class A a => B a where ...
class        C a where ...

instance A a => C a where ...
instance B a => C a where ...

How to specify which C instance to apply?
ghc -fallow-{overlapping,undecidable}-instances complains
about the ambiguity.

I simply don't accept the situation when adding an instance or
declaration changes the meaning of a code that was legal before.
Because in the absence of such things I can easily predict the meaning
of any code: just find the definitions of all used names, and when
found we surely know everything. Haskell succeeded with avoiding
them AFAIK. In the presence of such things I must sometimes scan the
whole progam for things that might change the meaning of the code,
by e.g. specifying more specific instances, or by making an instance
that caused another instance to apply to a particular type. The same
kind of danger as with SML's constructor: one cannot be sure unless
he has proven the lack of something in the whole program.

> >> If the user puts so, then one proclaims that it is the same for the 
> >> result which way to choose.
> 
> > The compiler can't verify that, so I accept that it simply raises
> > an error, at least by default.
> 
> No, no. There are many things that the compiler cannot or would
> not verify. This is not a reason for reporting an error each time.

But IMHO it is most likely an error to make two instances of the given
class and types. Someone might have seen only one of these instances
and thought that it does apply. I could write one of those instances
not knowing the other, and the compiler silently picked one of them,
maybe not the one I wanted... The compiler does not know if they
really behave the same or not. It would be dangerous to assume that
they always do.

> For example, to compute *correct*,  List.sort  needs (<) to possess
> certain properties, like transitivity, at a type `a'.  Clearly,
> the compiler has not to try checking directly such properties,
> unless, maybe, it is asked specially.

Here there is no ambig^H^H^H^H^Hoverlap. What I tried to write (sorting
using a relation that does not define an order) makes no sense at all.

> > I'm not convinced. It's much simpler when the language semantics are
> > deterministic.
> 
> No. A spot of indeterminism is good style.

I can hardly think about such cases in programming languages.

(Unless it's really hard to make it deterministic, like concurrency.
Life is hard. I know I have to be careful with concurrency.)

> > Haskell specifies the order in such cases. It's ((i+j)+k)+l.
> 
> I wrote that it is often good for the user not to think of how to
> set these parentheses. By the way, in some situations, the compiler 
> has right to set them differently.

Only if it can prove that it does not change the meaning, so it
basically allows nothing special - the compiler of any language is
allowed to transform a program in a way that does not change its
meaning in some sense. And IMHO it rarely changes the efficiency,
at least in a language with large general overheads.

If I write a Num instance with a non-associative (+), I will expect
that the compiler won't change the parentheses. I wouldn't write such
instance to avoid confusion, but the language definition is clear.

> I do not know what are the C++ templates.

They, together with the rules of overloading, allow a kind of
overlapping instances, choosing the "best fitting" function and
reporting an ambiguity error if there is more than one function with
the same level of "appropriateness" or "closeness". Similarly for
parametrized types (class templates, not function templates as above;
function templates are Haskell's polymorphic functions), with different
rules. The rules are very complex, not only because of overlappings.
The description of templates in the language standard has about 100kB
od text.

In particular for class templates there is a concept of complete
specialization (a two parameter type is defined like this, but when
the types are exactly A,B it is like that) and partial specialization
(if the second argument is C, it is like this; or if the first argument
is the pointer to some type T and the second argument is the pair
of the same T and int, etc.). For function templates there is only
complete specialization, but functions may be arbitrarily overloaded,
so with appropriate rules for partial ordering of templates that apply
for a given function call, the best match is chosen or an ambiguity
is reported.

> > This means that these cases are not "generic" and "special"
> > respectively. The essence of being generic is that the same thing
> > is applicable to many cases. The essence of being a special case of
> > something is that everything that is applicable generically to that
> > thing applies to us as well, but not necessarily the opposite.
> 
> I meant that the generic implementation works at a wider range
> of cases.

It does not, because sometimes a more specialized one replaces it.

>   instance Euclidean a => Set (ResidueE a) 
>     where
>     card (Rse _ b) = expensiveGenericMethodForCard b
>     ...
>   instance Set (ResidueE Integer) where  card (Rse _ b) = Fin b
>                                          ...
>   instance Field a => Set (ResidueE (UPol a)) where  
>                                               card _ = Infinity
>                                               ...

The first instance is a problem, because it does not apply for
all cases of ResidueE a (or at least is too expensive to be used
for all cases). I guess that instances of set should be separately
specified for various types of the form ResidueE x where x is some
more concrete type. Some of them will be similar, just calling
expensiveGenericMethodForCard. This has the disadvantage that
an instance must be repeated for all types that require distinct
implementations, but the advantage is using a clear type system (and
if expensiveGenericMethodForCard does not really work correctly for
all cases, that in no case the wrong instance wil be picked).

> > If a function should not be used for a particular type, the type
> > should not have been declared as an instance of some appropriate class.
> 
> According to the above settings,     expensiveGenericMethodForCard
> should not be used for a particular type         ResidueE Integer.

Yes.

> Then, as you suggest                             ResidueE Integer
> should not have been declared as an instance of  Set.

No, because expensiveGenericMethodForCard should not have been
used in the first place in the general instance. There should be no
general instance because some specific instances require a different
implementation.

Or, especially if there are several classes like Set that should
have generic instances for ResidueE a and specific instances for
specialized variants of ResidueE (but not necessarily), then it may
help to group properties of ResidueE in a single class, make a generic
Set instance of ResidueE for types that belong to that class, similarly
to all the other classes like Set, and then play with instances of that
class. There can be default method implementations, so some (or most)
instances will need not to define any methods explicitly. I think
that this all causes no problem for quite standard Haskell.

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