Simon Peyton-Jones <[EMAIL PROTECTED]> writes on 8 Mar 2000

> There has been a great deal of mail about overlapping 
> instances.  I confess that I have read little of it.
> But I am interested in it.  
>
>       Would someone like to write a summary of
>               what the issues are
>               what people agree about
>               what they disagree about
>       (as briefly as poss)?
> [..]


A harsh thing to ask, but Simon, maybe, you read these letters from
archive?
For some of my doubts remain un-answered. I mean mainly my last 
question to Jeffrey Lewis.

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



--------------------------------------------------------------------
      Discussion on overlapping instances in Haskell language.
      Summary by Sergey Mechveliani.  February 2000.

Participants:
Sergey Mechveliani         <[EMAIL PROTECTED]>     (M)
Marcin 'Qrczak' Kowalczyk  <[EMAIL PROTECTED]>    (K) 
Jeffrey Lewis              <[EMAIL PROTECTED]>   (L)
Fergus Henderson           <[EMAIL PROTECTED]>      (H)


M> Overlapping instances  ( OI )   look desirable. I ask Haskell to
   understand OI, to possibly relax the restrictions on OI,  and
   *if find them consistent*, include them in  Haskell-2.
   OI allow to specify different ways to compute the same thing: in
   a generic case (C a..)=>,  and in a special case, for example, 
   for some particular type construction. Two examples shown:
         matrixDeterminant,  cardinality for the domain of residues.
   Suggestion 1. Relax restrictions on OI 
     (in existing extensions). Resolve OI according to 
     (1) type context,   (2) type expression specialization,
     (3) priorities set.
   Suggestion 2. Deduced contexts.
     Example.  f :: Eq a => a -> Bool       f x = Just x == Just x
               instance Eq (Maybe Bool) ...
     The visible OI for  Eq  for  Maybe  makes existing compilers to
     force the user to write here  f :: (Eq a, Eq (Maybe a))...
     Instead, the compiler has to insert `Eq (Maybe a)' silently and
     continue. This changes interface module, the user source remains 
     with `Eq a =>' only.
     Reason:
     Eq a  has to mean all infinitely many things that can be deduced
     from this according to all visible items and instances.
     Hence, the above two type declarations have to mean the same.
     It is technical business of compiler which of equivalent type
     context signatures to take as intermediate auxiliary data.

K> OI are inconsistent with the rest of Haskell. 
   (K1) The meaning of program becomes not unique.
        The compiler does not know whether several user instances 
        yield the same result.
        Forgetting some import may change the result.
   (K2) Forgetting some import may change silently the run-time 
        behavior, and change the computational cost many times.
   (K3) Lengthy additional contexts appear in the type declarations
        due to OI visible. 
   (K4) (K3) may damage the code efficiency: 
        extra dictionaries to pass or something ...
   (K5) It may be hard to agree OI with local universal quantifiers,
        existential quantifiers
        (correct me, please, if I name them wrong!  - Mechveliani).
   (K6) Example (simplified slightly by Mechveliani).
     How to compile this? Looks like compiling E.e  needs to see the
     implementation of  F.f  - ?
                module F (f) where
                f :: (Eq a, Eq (Maybe a)) => a -> Bool
                f                            x =  (Just x)==(Just x)
                instance Eq (Maybe Bool) ...
                ...
   (K7) I cannot imagine a sensible implementation of the function:
               h :: Eq a => a -> a -> Int
               h x y = if x == y then 0 else 1 + h [x] [y]
     which would make h "1" "2" return 7 if in some other module 
     there is:
               instance Eq [[[[[[[String]]]]]]] where
                                       x == y = length x == length y

H> Deduced context suggestion breaks the shared library possibility
   ...
--------------------------------------------------------------------
With what the participants seem to agree:

* Forgetting some import may change silently the run-time 
  computational cost.
  OI need clever warnings - is this ever possible to help?

* If the programmer uses OI, and the compiler applies the 
  *context deducing* technique, and the program aims to link to 
  object library,
  then this is impossible, unless the library sources are given.

* if the local universal quantifiers, existential quantifiers ever
  present a problem to agree them with OI,
  forget of these quantifiers, so far, when considering OI.
--------------------------------------------------------------------

Glimpses of discussion:

M> (K6) stucks me ...
M> (next letter): No, no problems. We guess how they compile this...

L> Yes, existing implementations act this way.

M> On (K7): the only problem I see is that 7 brackets in OI cause, 
   with existing compilers, about (7^2)/2 brackets to appear in
   additional context  Eq [a], Eq [[a]] ..  for  h.
   A good example in favor of  deduced context  suggestion.
   On  (K7), (K4):  the code will not be slower, nor more complex 
   than the program like (K7) "asks".

L> (edited by Mechveliani) 
   I may suggest how to compile this ...  And indeed, too many 
   additional `[' to appear in context of  h.
   But is this a real problem?

(M) On (K1):  with OI, a program meaning is still unique.
    It is defined by all the items, instances in the scope,
    and by certain fixed rules to resolve OI.
    Forgetting some import is not likely to change the result, 
    because OI are needed to compute the *same* result in different
    ways, so, they are defined respectively.

(M) class Cast a b ...  helps my program to cast between domains 
    (types). But it tends to lead to OI, and it is desirable for OI
    restrictions to relax.

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

(M) Some attempts had lead to the ambiguity and compile errors. 
    Therefore, I defined less casting instances, more modest than 
    initially aimed. This helps. At least, if this all compiles and
    works, what inconsistency may then appear?

(K) The compiler cannot check whether the overlapping instances
    define the same result.

(M) The compiler has not to be supposed to check this.
    The user may even deliberately diverse the results - 
    preserving the *user meaning*.
    Example: the two OI may return expression for polynomial  op ..
    as  "x^2 + 1",  and  "x^2 + 0*x + 1"  respectively.
    If the user program considers them as equivalent, then this
    difference may cause no harm, sometimes may help.

Reply via email to