I continue arguing for the overlapping instances.
To my

>> It may know how to compute an operation in a more efficient way in 
>> the special case, and in a less efficient way in the generic case.

Marcin 'Qrczak' Kowalczyk  <[EMAIL PROTECTED]>  writes on 6 Feb 2000

> But in a case where it's only a matter of efficiency, it is not so
> dangerous if careful imports etc. can fix it.

It is dangerous, in the following sense. 
Some functions may become slower in 10 times, in 100 ... - 
depending on the data - unless the import is carefully fixed.
And how to make sure of the import?


>> > If it does not know, it should not specify it.

>> There are often several operations in a class. Each operation may
>> have its own most generic situation in which it is known how to
>> compute. This does not look like a sufficient reason to split this
>> class into several classes, each with a single operation.

> Sorry, life is hard. Anyway, I don't see a place for returning Unknown
> values. Should really the fact that cardinality is known or not be
> computed at runtime? Why is cardinality not in a separate class which
> have instances *only* for types where it is known?

Let us forget of `Unknown'. The programmer can eliminate this.
The difference is in the efficiency of generic and special methods.

> Sorry, life is hard. 

Denying overlapping instances is likely to make it harder - for the 
users.


>> A good example for overlapping instances: the matrix determinant:
>>                det mt,  mt :: [[a]]  n by n  matrix.
>> 
>> I know the following good ways to compute it.
>> [..]

> I would probably:
> - define separate functions for each algorithm, each with correct
>   requirements in its type,
> - define a class with a generic determinant function,
> - make its instances for each possible type or type constructor,
>   manually choosing the algorithm that fits best.

This is to make it easier for the Haskell implementors.
And I would like it to fit the most natural habit of specifying
scientific computation.


> And overlapping instances themselves can be lost because of context
> reduction, where a polymorphic function will use the generic instance
> of something else instead of the specific one - I can think about an
> example if it's unclear.

The compiler needs special care for the overlaps when reducing the 
contexts.

> 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?


>> > There are ambiguities if something was defined as "if it's X then
>> > it's Z, if it's Y then it's Z, it's X, it's Y" - but *how* it 
>> > should be Z - basing on X or Y?
>> 
>> 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.
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.
Such examples are met everywhere.


> At most it could be explicitly marked by the programmer that whenever
> there is an ambiguity between certain definitions, it does not matter
> which to use because they all produce the same result. 
> [..]

This is an overlap, better not to call it ambiguity.
The compiler has to issue the warnings of overlaps.

> I'm not convinced. It's much simpler when the language semantics are
> deterministic.

No. A spot of indeterminism is good style.
And it preserves, in principle, more room for the optimization.
For example, in the scientific computation, the main part in a 
program has usually to be non-deterministic, it is axiomatic, 
describes the equality relation. Though, a program may include
also the strategy hints, in what order and direction to apply some 
rules. And this indeterminism is in the very air of the lambda 
calculus related to the Haskell origin.


>> For example, a programmer often writes   i+j+k+l :: Integer 
>> and does not care of many different ways in which this may evaluate.

> 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.
Probably, the language report has to say here that it sets 
             *any* parenthesis structure equivalent to  ((i+j)+k)+l.
It depends on the program fragment which structures are equivalent 
to it and which are better to compute.


>> For the case with  "if it's X ...",
>> the way has to be chosen according to the
>>   (1) type context,
>>   (2) type expression specialization,
>>   (3) priorities set.
>> If the user omits the priorities, the compiler sets the defaults.
>> What the recent implementations have, is (2).
>> Sadly, this does not do in full the above example with  det.
>> And I think, I could set the priorities for the above cases
>> (C)...(FFP)  for  det.

> I cannot think about an elegant solution which would allow specifying
> selection of the best method automatically. Semantics of classes
> are already complex without it. I certainly don't want to reach the
> complexity of C++ templates, which are almost impossible to understand
> fully in details and are a nightmare to implement correctly.

I do not know what are the C++ templates. 
The compiler does not has to choose the best method. It has only to 
choose the most special one - by construction + priorities.
GHC, Hugs have recently certain way to treat overlaps.
I wonder in what way it may develop.
My suggestions with (1),(2),(3) were made long ago and wait their
criticism.
Personally, I had not thought so far about their possible design 
principle. 
At least, I have to understand first why the user is forced 
sometimes to write a non-reduced context, why the compiler cannot 
do the business.


>> >      If a generic implementation does not work for this
>> > case, either it is not a special case of the generic case, or the
>> > generic implementation is wrong itself. 
>> > A generic implementation should work correctly for all special 
>> > cases - that's why it is placed in a generic place and called 
>> > generic.
> 
>> A strange objection. The situation is that the generic implementation
>> does work in the generic case and the special one works in the
>> special case.

> 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. The phrase
  "The situation is that the generic implementation does work in the 
   generic case and the special one works in the special case.
  "
does not contradict this meaning.


> 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.

I suspect this is not so. 
It is a good point to introduce an example.
And, sorry, it is again computer algebra.
Consider the domain constructors 
  Integer, 
  UPol       for univariate polynomial,
  Rse        for the Residue domain.
------------------------------------------------------------------
  data {-Euclidean a=>-}  ResidueE a = Rse a a  ...

For example,                  Rse 1 4  :: ResidueE Integer 
is the residue of 1 modulo 4.    
The domains                   Integer,  Field a => UPol a

are supplied naturally with the operations of remainder-division 
and  eNorm.  This is called an Euclidean ring:

  class (Num a, ...) => Euclidean a where divRem :: a -> a -> (a,a)
                                          eNorm  :: a -> Integer
  instance Euclidean Integer where divRem = quotRem
                                   eNorm  = abs
  instance Field a => Euclidean (UPol a)  where
                               divRem = divRemOfPolynomials
                               eNorm  = leadingExponentOfPolynomial

And there exist other constructors supplied with the instance of
Euclidean.
The aim is to define the Set operations for the residue domain.

  type Card = Fin Integer | Infinity     -- for cardinality of a set

  class Set a where card :: a -> Card          -- argument is sample
                    ...
                    -- some other operations, skip them, so far
                 -- Examples:  
                 -- card (0::Integer) = card (1::Integer) = Infinity
                 -- card True         = card False        = Fin 2
                 -- card (Rse 1 4)    = card (Rse 2 4)    = Fin 4

  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
                                              ...
-----------------------------------------------------------------
To my mind, this is the most natural setting.
It copies the mathematical practice.
And the three instances have to overlap.

> 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.
Then, as you suggest                             ResidueE Integer
should not have been declared as an instance of  Set.
But this is clearly, not the point.
Unless I have misunderstood the objection.
How the above settings can be expressed naturally without 
overlapping instances?
Besides, certain other constructors wait to be supplied with the
above instances.


------------------
Sergey Mechveliani
[EMAIL PROTECTED]

Reply via email to