From: Greg Menke
Subject: Specialized equal
Date: 
Message-ID: <m3r8r0dm01.fsf@europa.pienet>
I think I have the need to do something like a specialized #'equal and
#'equalp so I can test 2 instances of a class using the normal suite
of equality functions.

I tried to defmethod an variation of #'equalp to perform these tests &
discovered it itsn't a generic function and thus can't be specialized
(I think I got that right).

Is the right solution to use 'myclass-equalp` kinds of functions or is
there a CLOS-aware variation of the eq* suite of functions I could
use instead?  A fairly close search of CLHS didn't show anything, but
I could've easily missed it.

Thanks,

Gregm

From: Barry Margolin
Subject: Re: Specialized equal
Date: 
Message-ID: <OnSI7.8$I25.1703@burlma1-snr2>
In article <··············@europa.pienet>,
Greg Menke  <··········@mindspring.com> wrote:
>Is the right solution to use 'myclass-equalp` kinds of functions or is
>there a CLOS-aware variation of the eq* suite of functions I could
>use instead?  A fairly close search of CLHS didn't show anything, but
>I could've easily missed it.

You should use your own function.  Equality isn't something that's
type-dependent, it's application-dependent.

Kent has a white paper on the whole issue of copying and equality, and I'm
sure he'll chime in with the URL.

-- 
Barry Margolin, ······@genuity.net
Genuity, Woburn, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwr8r0uf8o.fsf@shell01.TheWorld.com>
Barry Margolin <······@genuity.net> writes:

> In article <··············@europa.pienet>,
> Greg Menke  <··········@mindspring.com> wrote:
> >Is the right solution to use 'myclass-equalp` kinds of functions or is
> >there a CLOS-aware variation of the eq* suite of functions I could
> >use instead?  A fairly close search of CLHS didn't show anything, but
> >I could've easily missed it.
> 
> You should use your own function.  Equality isn't something that's
> type-dependent, it's application-dependent.

I think of it as multi-dimensional.  There is no such generic concept as
equality.  There is equality-for-a-purpose, and there are many purposes.

It is unfortunate that the functions eq, eql, equal, equalp appear
(probably falsely) to be all of a kind, arranged along a certain
one-dimensional space of generality of equality.  In fact, equality is
a complex multi-dimensional space with very different shape depending
on the purpose.  For example, equal-as-expression-structure,
equal-as-lisp-semantic-expressions, equal-as-fortran-semantic-expressions,
equal-as-paperweight, equal-as-cook, equal-as-typist, equal-as-friend,
even if all generic, are not linearly arranged.  And they may be BOTH
type-dependent AND as each a different "application" of equality (to use
Barry's term) also application-dependent.
 
Some of this is just so much abstract philosophy, but the concrete
importance is: It is, to many, a letdown not to be able to customize
EQUAL because everyone likes to think themselves and their
application-of-the-day as the center of the universe.  Programmers
must not get into a turf war trying to redefine the meaning of the one
and only one EQUAL because there is not one and only one single
meaning of equality.  And the attempt to shoehorn things into one
function is what causes this.

I took the controversial position of asking that EQUAL not be included in
the language because of the confusions it evokes.  Doubtless most people 
are just as happy I lost this argument because there is something handy
about the vague bluntness of EQUAL and EQUALP.  And maybe it's just as well
these names are taken by something not very general because it means that 
the name isn't empty-and-waiting-to-be-pounced-upon.  But don't confuse
the notion of a "blunt" EQUAL with the notion of a "general purpose" EQUAL.
Hammers are useful for a great many household needs, too, but not all of
them are good style that you would build layered product upon...  Production
techniques, to be of refined and reliable quality, often have to develop
their own "hammer-substitutes", that is, their own more-appropriate tools.

> Kent has a white paper on the whole issue of copying and equality, and I'm
> sure he'll chime in with the URL.

http://world.std.com/~pitman/PS/EQUAL.lisp
From: Greg Menke
Subject: Re: Specialized equal
Date: 
Message-ID: <m34rnvhnha.fsf@europa.pienet>
Kent M Pitman <······@world.std.com> writes:

> Barry Margolin <······@genuity.net> writes:
> 
> 
> > Kent has a white paper on the whole issue of copying and equality, and I'm
> > sure he'll chime in with the URL.
> 
> http://world.std.com/~pitman/PS/EQUAL.lisp

Thanks!

Greg
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwu1vv4zp2.fsf@shell01.TheWorld.com>
Greg Menke <··········@mindspring.com> writes:

> Kent M Pitman <······@world.std.com> writes:
> 
> > Barry Margolin <······@genuity.net> writes:
> > 
> > 
> > > Kent has a white paper on the whole issue of copying and equality, and I'm
> > > sure he'll chime in with the URL.
> > 
> > http://world.std.com/~pitman/PS/EQUAL.lisp

er, .html

sorry

(Lisp on the brain.)
From: Juliusz Chroboczek
Subject: Re: Specialized equal
Date: 
Message-ID: <87u1vts33r.fsf@pps.jussieu.fr>
Kent M Pitman:

KP> It is unfortunate that the functions eq, eql, equal, equalp appear
KP> (probably falsely) to be all of a kind,

Well, EQL has a very specific role in Lisp's semantics: it is
reference equality.  In order to be able to say that an object is
something with an identity, and that all Lisp values are references to
objects, we need to know what it means to be ``the same'' reference,
i.e. for two references to point at objects with the same identity.
In short, EQL is the fundamental tool that allows us to reason about
Common Lisp programs.

As to EQUAL and EQUALP, I would tend to agree with you that they are a
different breed, as there is nothing fundamental about them, but are
merely somebody's application's notion of extensional equality that
has turned out to be more generally useful.

However, while I do agree that allowing the user to customise EQUAL on
built-in datatypes is dangerous, I don't think it would be absurd to
allow him to do so on his own classes.  After all, the necessary
modularity is already ensured by the class system.

To follow up on your example, say I write

  (in-package "COOKING")

  (defclass cook (...) ...)

then it is quite sensible for me to specialise EQUAL on (COOK COOK) to
mean EQUAL-AS-COOK.  The only code that can ever invoke my method is
code that is already using my library (how would it create COOK instances
otherwise?).

                                        Juliusz

P.S. EQ I don't claim to understand.  Consider for example the following:

      (defun foo (x y)
        (declare (type (signed-byte 32) x y))
        (let ((x* x) (y* y))
          (eql (eq x y) (eq x* y*))))

    What if the values of X, Y are small bignums and X*, Y* full-word
    integers?  Would returning false from FOO be comformant?

    Either way, yuck.
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwzo5hxs58.fsf@shell01.TheWorld.com>
Juliusz Chroboczek <···@pps.jussieu.fr> writes:

> However, while I do agree that allowing the user to customise EQUAL on
> built-in datatypes is dangerous, I don't think it would be absurd to
> allow him to do so on his own classes.  After all, the necessary
> modularity is already ensured by the class system.

I'm not so sure I believe in this, but my point was two-fold:

First, customizing EQUAL means customizing hash table support.  We don't
offer you a way to do the latter, so EQUAL per se can't be customized
until that's solved.  You *could* make an == operator that wasn't a valid
test for hash tables, though.

But second, although I think you're right that for a given application, you
can mostly control things so user-defined EQUAL doesn't run out of control,
I think we'd need to specify the meaning of == (or whatever you call it) 
better if the generic function was to have any coherent meaning when dealing
with heterogeneous data.  I'd bet people would, by default, not always put a 
lot of thought into what they meant to achieve with EQUAL, thinking it was
about _their_ application and not about other programs that might inspect,
order, compose, etc. their data.  Any such generic is by definition a shared
resource, and one thing we learned about generics early on that caused us
not to go generic-happy with all of our operators, even though we could have,
is that you have to specify the definition better (in English, I mean)
than people often do if you want to avoid things like "foo"+"bar" = "foobar"
kinds of effects.

 
> To follow up on your example, say I write
> 
>   (in-package "COOKING")
> 
>   (defclass cook (...) ...)
> 
> then it is quite sensible for me to specialise EQUAL on (COOK COOK) to
> mean EQUAL-AS-COOK.

No, becasue the point is that

 (equal-as-cook cowboy:*default-cowboy* cook:*default-chef*)

might need to return true while 

 (equal-as-horseback-rider cowboy:*default-cowboy* cook:*default-chef*)

needs to return NIL.  Merely having an EQUAL method on cook and cowboy
does not accomplish this.

> The only code that can ever invoke my method is
> code that is already using my library (how would it create COOK instances
> otherwise?).

But your library, if it's at all general, has many uses.  Not just the
application you originally wrote it for.

> 
>                                         Juliusz
> 
> P.S. EQ I don't claim to understand.  Consider for example the following:
> 
>       (defun foo (x y)
>         (declare (type (signed-byte 32) x y))
>         (let ((x* x) (y* y))
>           (eql (eq x y) (eq x* y*))))
> 
>     What if the values of X, Y are small bignums and X*, Y* full-word
>     integers?  Would returning false from FOO be comformant?
> 
>     Either way, yuck.

Yes, I think so.  The reason is that you have to assume integers might live
in individually adressable registers, even if they seemed like the same object.
EQL papers over this kind of register-to-register motion.
From: Alexey Dejneka
Subject: Re: Specialized equal
Date: 
Message-ID: <m3snb9qrq2.fsf@comail.ru>
Juliusz Chroboczek <···@pps.jussieu.fr> writes:
> P.S. EQ I don't claim to understand.  Consider for example the following:

EQ works with `objects' (in OOP sense: they can be changed, keeping
their identity, as a baby growing to an adult); numbers are not
`objects': how could you change 1 to be 2 (*)? EQL works with
`objects' and numbers - it is the difference.

> 
>       (defun foo (x y)
>         (declare (type (signed-byte 32) x y))
>         (let ((x* x) (y* y))
>           (eql (eq x y) (eq x* y*))))
> 
>     What if the values of X, Y are small bignums and X*, Y* full-word
>     integers?  Would returning false from FOO be comformant?

Yes: From CLHS:

|  (eq 3 3)
|   =>  true
|   OR=>  false
...
| An implementation is permitted to make ``copies'' of characters and numbers at any
| time. The effect is that Common Lisp makes no guarantee that eq is true even when both
| its arguments are ``the same thing'' if that thing is a character or number.

Regards,
Alexey Dejneka

--
Notes:

(*) FORTRAN programmers know...

-- 
Greenspun's Tenth Rule of Programming as a reclame of Fortran
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwadxh5jry.fsf@shell01.TheWorld.com>
Alexey Dejneka <········@comail.ru> writes:

> Juliusz Chroboczek <···@pps.jussieu.fr> writes:
> > P.S. EQ I don't claim to understand.  Consider for example the following:
> 
> EQ works with `objects' (in OOP sense: they can be changed, keeping
> their identity, as a baby growing to an adult); numbers are not
> `objects': how could you change 1 to be 2 (*)?

Numbers ARE objects.  They just have metaclass BUILTIN-CLASS.  You mean
to say they are not STANDARD-CLASS, but that's potentially true for a 
number of built-in types.  Symbols, for example, are also objects even
though you can't use CHANGE-CLASS on them.

(And, in answer to your question, in old MACLISP, before CL, we used to do
 it with RPLACD, which changed the right half of the word. If you
 hadn't gensym'd the number, though, you were bashing a system-wide
 constant.  But some applications did generate bignums, which were not
 interned like little numbers were in MACLISP, and then RPLACD them
 to have small values again.)

> EQL works with `objects' and numbers - it is the difference.

Actually, it works more like this, from an evolutionary and practical
point of view:

EQL should have been called EQ.  It portably treats numbers as numbers
wish to be treated: as first class objects with identity.

The problem is that doing this is slightly slower in a way that was 
critically important to speed in some implementations.  Some people really
know they can get away with EQ and so need to have it there.

EQ is fast, but it exposes the implementation of things best left abstract.
So its effect (except on non-numbers/chars) is non-portable.

Portably speaking, everyone should always _think_ in terms of EQL and
pretend EQ doesn't exist, except that EQ is faster and can be used as
an optimization if you know your data is non-numbers/chars.  Or they
can think in terms of EQ, and just use EQL to get the portably
reliable effect when they are using data that requires it.

But really, you shouldn't think of these as two different functions.
Rather, you should think of them as two views on the same conceptual
operation.

The same effect could, I suppose, have been achieved with one function
and a lot of type declarations, but it would have been messy.
From: Alexey Dejneka
Subject: Re: Specialized equal
Date: 
Message-ID: <m31yiselrd.fsf@comail.ru>
Hello,

Kent M Pitman <······@world.std.com> writes:

> Alexey Dejneka <········@comail.ru> writes:
> 
> > Juliusz Chroboczek <···@pps.jussieu.fr> writes:
> > > P.S. EQ I don't claim to understand.  Consider for example the following:
> > 
> > EQ works with `objects' (in OOP sense: they can be changed, keeping
> > their identity, as a baby growing to an adult); numbers are not
> > `objects': how could you change 1 to be 2 (*)?
> 
> Numbers ARE objects.  They just have metaclass BUILTIN-CLASS.  You mean
> to say they are not STANDARD-CLASS, but that's potentially true for a 
> number of built-in types.  Symbols, for example, are also objects even
> though you can't use CHANGE-CLASS on them.

No, I did not mean neither formal sense, nor implementational, and I
know that CLHS calls numbers "objects".

> EQ is fast, but it exposes the implementation of things best left abstract.
> So its effect (except on non-numbers/chars) is non-portable.
...
> But really, you shouldn't think of these as two different functions.
> Rather, you should think of them as two views on the same conceptual
> operation.

I see the *conceptual* difference between comparing strings and
numbers. A string have both an identity and a value, and they are
different. But for (mathematical) numbers [of the same type] there is
no difference between this notions -- there is no other identity,
except for equality of values. Many languages, which I know, do not
possess numbers -- but cells, containing a representation of a
number. The best example of number `objects' (in my sense,
i.e. mutable) shows the following Fortran program:

      PROGRAM SHOW
        DO 10 I=1,5
           CALL SUB(1)
 10     CONTINUE
      END

      SUBROUTINE SUB(I)
        WRITE (*,*) I
        I = I + 1
      END

In some implementations it prints 1 2 3 4 5. 

(Of course, Fortran language have no `number objects' -- but some
implementations shows consequences of such approach.)

But I see no possibility to do it in CL.

Numbers are different from most other "CLHS objects".

---
(sorry for the answer in the same letter)

Jochen Schmidt writes:

> And be ensured that both behaviors EQ _and_ EQL is useful because it might 
> be _very_ interesting for some applications to compare non-immediate 
> numbers like bignums by reference! (Think of topics like 
> ressource-management, memory-management a. s. o.)

I am afraid that comparing bignums with EQ is portable, but not conforming.


Regards,
Alexey Dejneka

-- 
Greenspun's Tenth Rule of Programming as a reclame of Fortran
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwheroliky.fsf@shell01.TheWorld.com>
Alexey Dejneka <········@comail.ru> writes:

> I see the *conceptual* difference between comparing strings and
> numbers. A string have both an identity and a value, and they are
> different. But for (mathematical) numbers [of the same type] there is
> no difference between this notions -- there is no other identity,
> except for equality of values.

No, what you mean to say is that numbers have no defined mutators and
strings do.  This is not the same thing.

Likewise pathnames have no defined mutators.  Would you say they are not
objects?  You can certainly ask for their parts, but then you can do this
for a float as well, asking for its mantissa, etc.  In what sense is
this different?

> Many languages, which I know, do not
> possess numbers -- but cells, containing a representation of a
> number. The best example of number `objects' (in my sense,
> i.e. mutable) shows the following Fortran program:
> 
>       PROGRAM SHOW
>         DO 10 I=1,5
>            CALL SUB(1)
>  10     CONTINUE
>       END
> 
>       SUBROUTINE SUB(I)
>         WRITE (*,*) I
>         I = I + 1
>       END
> 
> In some implementations it prints 1 2 3 4 5. 
> 
> (Of course, Fortran language have no `number objects' -- but some
> implementations shows consequences of such approach.)

This is confusing "objectness" with "calling sequence".  Fortran uses
call-by-reference.  The address passed is the location that held the
value, not the value itself.  (Ironically, in most languages that call
themselves call-by-value, the value is not passsed but a copy of the
value.  For many years, Lisp called itself call-by-value since it
passes the value, not the location of the value.  But I prefer to call
this call-by-identity.)
 
Lisp could be call-by-reference and the same would happen as in your
Fortran program.  But it didn't make the choice to do that.  What you are
seeing in a case of integer args vs other args is not a difference in how
the calling is done, but in the fact that some objects have defined mutators
and some do not.

> But I see no possibility to do it in CL.
> 
> Numbers are different from most other "CLHS objects".

I believe you are confused on material points here that are leading
you to wrong conclusion here.

> ---
> (sorry for the answer in the same letter)
> 
> Jochen Schmidt writes:
> 
> > And be ensured that both behaviors EQ _and_ EQL is useful because it might 
> > be _very_ interesting for some applications to compare non-immediate 
> > numbers like bignums by reference! (Think of topics like 
> > ressource-management, memory-management a. s. o.)
> 
> I am afraid that comparing bignums with EQ is portable, but not conforming.

I think can sometimes be also conforming, though only in limited
cases.  You just have to use it in a way that doesn't presuppose a
particular result.  That's not easy.  But, for example, the following
is both portable and conforming:

(let* ((big1 (1+ most-positive-fixnum))
       (big2 (1+ most-positive-fixnum)) 
       (exp `(eq ,big1 ,big2)))
  (format t "~&~S sometimes returns ~S in this implementation.~%"
          exp (eval exp)))

It is so because it depends on things that are reliably present and does
not rely on any behavior beyond what is defined by the standard.  That is,
either result of the EQ expression would make the English text output
correct.
From: Jochen Schmidt
Subject: Re: Specialized equal
Date: 
Message-ID: <9te8s9$am5$1@rznews2.rrze.uni-erlangen.de>
Alexey Dejneka wrote:

> Juliusz Chroboczek <···@pps.jussieu.fr> writes:
>> P.S. EQ I don't claim to understand.  Consider for example the following:
> 
> EQ works with `objects' (in OOP sense: they can be changed, keeping
> their identity, as a baby growing to an adult); numbers are not
> `objects': how could you change 1 to be 2 (*)? EQL works with
> `objects' and numbers - it is the difference.

I don't think that saying numbers are no object is right here - they _are_ 
objects. It is right that EQ is about testing "identity" of objects though.
In the case of numbers the concept of "identity" can be ambiguous. 
Mathematically spoken the object '3' is one and the same object regardless
on where it may appear (letting aside questions like modular rings and such
things where multiple different numbers may be equivalent in their 
class...). On the other side we are programming in concrete programming 
languages on real computers and therefore we have to take into account that
there could be another notion of identity for numbers in that context.

Testing for identity is easily done by a pointer comparison. The question 
is if EQ returns T for _immediate_ objects like FIXNUM or characters. Many 
implementations simply compare the "object-descriptor" (I don't know how 
this is really called sorry) which is either representated by a pointer or 
some immediate value with some type bits added. In those implementations EQ 
comparison of two fixnums with the same value yields T.
On the other hand - bignums are not represented as immediate objects but 
pointers to their data. Therefore two bignums that have the same _value_ 
and therefore would be mathematically equivalent may _not_ be EQ since they 
may be at different places in memory. Here is where EQL comes in by 
comparing numbers explicitely "by value".
And be ensured that both behaviors EQ _and_ EQL is useful because it might 
be _very_ interesting for some applications to compare non-immediate 
numbers like bignums by reference! (Think of topics like 
ressource-management, memory-management a. s. o.)

ciao,
Jochen

--
http://www.dataheaven.de
From: Erik Naggum
Subject: Re: Specialized equal
Date: 
Message-ID: <3215280566337392@naggum.net>
* Jochen Schmidt
| Testing for identity is easily done by a pointer comparison.

  I think it is most pedagogical to quickly say that eq compares machine
  words with machine instructions and then make sure that you answer "use
  eql, instead" when the newbie asks about the internal representation of
  Lisp objects.  I would say that eq is for advanced users.

  If a machine word cannot hold a number, it needs to be stored elsewhere.
  This is the difference between a fixnum and bignum.

| And be ensured that both behaviors EQ _and_ EQL is useful because it
| might  be _very_ interesting for some applications to compare
| non-immediate  numbers like bignums by reference! (Think of topics like
| ressource-management, memory-management a. s. o.)

  I think the more important reason is that eq can, and is expected to, be
  implemented with a single machine instruction, while eql has no upper
  bound on its execution time.  (Consider comparing for equality when the
  numbers differ only in the bit compared last, and that there is no upper
  bound on the number of bits in a number.)  If eq is true, eql is true,
  but if eq is false, eql can only be true if the object types are eq and
  are numbers.  So the cost of eql is relatively small until you compare
  bignums or floats, but if you know you are not comparing numbers, I
  prefer to make that knowledge explicit by using eq.

///
-- 
  Norway is now run by a priest from the fundamentalist Christian People's
  Party, the fifth largest party representing one eighth of the electorate.
-- 
  Carrying a Swiss Army pocket knife in Oslo, Norway, is a criminal offense.
From: Janis Dzerins
Subject: Re: Specialized equal
Date: 
Message-ID: <87elmsl926.fsf@asaka.latnet.lv>
Erik Naggum <····@naggum.net> writes:

>   If eq is true, eql is true, but if eq is false, eql can only be
>   true if the object types are eq and are numbers.

Let us not forget about characters (although the discussion is about
eq and eql as applied to numbers; but someone might forget to look up
the HyperSpec).

-- 
Janis Dzerins

  Eat shit -- billions of flies can't be wrong.
From: Jochen Schmidt
Subject: Re: Specialized equal
Date: 
Message-ID: <9te8tf$amd$1@rznews2.rrze.uni-erlangen.de>
Alexey Dejneka wrote:

> Juliusz Chroboczek <···@pps.jussieu.fr> writes:
>> P.S. EQ I don't claim to understand.  Consider for example the following:
> 
> EQ works with `objects' (in OOP sense: they can be changed, keeping
> their identity, as a baby growing to an adult); numbers are not
> `objects': how could you change 1 to be 2 (*)? EQL works with
> `objects' and numbers - it is the difference.

I don't think that saying numbers are no object is right here - they _are_ 
objects. It is right that EQ is about testing "identity" of objects though.
In the case of numbers the concept of "identity" can be ambiguous. 
Mathematically spoken the object '3' is one and the same object regardless
on where it may appear (letting aside questions like modular rings and such
things where multiple different numbers may be equivalent in their 
class...). On the other side we are programming in concrete programming 
languages on real computers and therefore we have to take into account that
there could be another notion of identity for numbers in that context.

Testing for identity is easily done by a pointer comparison. The question 
is if EQ returns T for _immediate_ objects like FIXNUM or characters. Many 
implementations simply compare the "object-descriptor" (I don't know how 
this is really called sorry) which is either representated by a pointer or 
some immediate value with some type bits added. In those implementations EQ 
comparison of two fixnums with the same value yields T.
On the other hand - bignums are not represented as immediate objects but 
pointers to their data. Therefore two bignums that have the same _value_ 
and therefore would be mathematically equivalent may _not_ be EQ since they 
may be at different places in memory. Here is where EQL comes in by 
comparing numbers explicitely "by value".
And be ensured that both behaviors EQ _and_ EQL is useful because it might 
be _very_ interesting for some applications to compare non-immediate 
numbers like bignums by reference! (Think of topics like 
ressource-management, memory-management a. s. o.)

ciao,
Jochen

--
http://www.dataheaven.de
From: Pierre R. Mai
Subject: Re: Specialized equal
Date: 
Message-ID: <87wv0kklr6.fsf@orion.bln.pmsf.de>
Juliusz Chroboczek <···@pps.jussieu.fr> writes:

> However, while I do agree that allowing the user to customise EQUAL on
> built-in datatypes is dangerous, I don't think it would be absurd to
> allow him to do so on his own classes.  After all, the necessary
> modularity is already ensured by the class system.
> 
> To follow up on your example, say I write
> 
>   (in-package "COOKING")
> 
>   (defclass cook (...) ...)
> 
> then it is quite sensible for me to specialise EQUAL on (COOK COOK) to
> mean EQUAL-AS-COOK.  The only code that can ever invoke my method is
> code that is already using my library (how would it create COOK instances
> otherwise?).

If that were true[1], then there wouldn't be any need to customize EQUAL
in the first place:  Since only code that is already using your
library will invoke it that way, it could use your EQUAL-AS-COOK
(either directly, or incorporating it into its own application
specific GF).

The whole idea of specializing EQUAL is to allow this method to
influence code that doesn't anticipate the existance of said method.
That is one of the main reasons of having GFs, namely allowing unknown
code to hook into that GF, in order to provide specialized behaviour
for its new classes.

The reason that EQUAL shouldn't be a GF is twofold:

a) It _is_ already specified for all types and classes, so any change
   will change specified behaviour.  So in one sense it is too late
   now, changing EQUAL would potentially invalidate large amounts of
   old code, for little gain.

b) We might instead create a new GF, EQUAL*, that was extensible.  But
   in order to do this, we would have to state the _precise_
   restrictions that new methods on this GF would have to obey, in
   order to allow the caller to know beforehand the consequences of
   calling EQUAL*.  Most OOP languages that have an extensible
   equality predicate punt on this, letting the specification be
   "compares two objects according to some random equality predicate.
   When this returns true, someone, somewhere, considered the two
   objects to be equivalent for some unknown purpose".  I fail to see
   the utility of a GF with such a lax specification.

   So we would have to be specific, and that means we would have to
   pick out one of the random ways equality could be usefully defined
   in some context.  But including such a random thing in the language
   would be really silly, much more so than including EQUAL...

Regs, Pierre.


Footnotes: 
[1]  It isn't true:  Code using EQUAL can get COOK instances through
     some third-party, that uses COOKING.  So the EQUAL-using code
     will get influenced by the new method on EQUAL, without knowing
     anything about COOKING, and the third-party knows about COOKING,
     but doesn't want to inspect potentially huge amounts of code for
     uses of EQUAL on passed-in objects.

-- 
Pierre R. Mai <····@acm.org>                    http://www.pmsf.de/pmai/
 The most likely way for the world to be destroyed, most experts agree,
 is by accident. That's where we come in; we're computer professionals.
 We cause accidents.                           -- Nathaniel Borenstein
From: Kent M Pitman
Subject: Re: Specialized equal
Date: 
Message-ID: <sfwofm4uew2.fsf@shell01.TheWorld.com>
Greg Menke <··········@mindspring.com> writes:

> I think I have the need to do something like a specialized #'equal and
> #'equalp so I can test 2 instances of a class using the normal suite
> of equality functions.

By the way, though I made some unrelated remarks on this under
separate cover, I wanted to add one reminder of an issue that is
often-overlooked whenever this question comes up:

EQUAL and EQUALP are "total" functions.  They are defined for all data.
Customizing these would be *re*defining the meaning of EQUAL and EQUALP
since absent such discussion, there is already a defined meaning.

Being able to customize any function which has been advertised to do
something and saying that it does something else breaks code that depends
on the other meaning.  You can say "yes, but this is a new kind of object"
but you have to remember that other programs may get data flow of your
object.  They may store it in hash tables that depend on certain consistent
qualities of these operators and table lookup may fail if that quality
is tinkered with.

The only reason youc an customize PRINT-OBJECT is that, in effect, the
definition of this includes the presence of customization; that is,
programmers are told from the very start that "you'd better not depend
on a whole lot out of this function except that it does I/O to the  
stream--the nature of the I/O is left vague".  So programs won't be broken
not because "customization is safe" but because "customization of things
advertised to be customizable" is as safe as you can get with these kinds
of things.
From: Tim Bradshaw
Subject: Re: Specialized equal
Date: 
Message-ID: <fbc0f5d1.0111190650.23bd8f9c@posting.google.com>
Kent M Pitman <······@world.std.com> wrote in message news:<···············@shell01.TheWorld.com>...
> 
> EQUAL and EQUALP are "total" functions.  They are defined for all data.
> Customizing these would be *re*defining the meaning of EQUAL and EQUALP
> since absent such discussion, there is already a defined meaning.

> [...]
> 
> The only reason youc an customize PRINT-OBJECT is that, in effect, the
> definition of this includes the presence of customization; that is,
> programmers are told from the very start that "you'd better not depend
> on a whole lot out of this function except that it does I/O to the  
> stream--the nature of the I/O is left vague".  So programs won't be broken
> not because "customization is safe" but because "customization of things
> advertised to be customizable" is as safe as you can get with these kinds
> of things.

I think this is one of those interesting issues that doesn't have a
really good answer (or anyway I don't know the answer!).

I often define GFs which either have default T methods (or (T T ...)
methods) which make a kind of sense for other classes, but have
methods for some more specific classes too.  For some of these it's Ok
for users to further define methods, for some it isn't.  I don't
really have a good way of describing whether this is OK or not except
clauses in the manual which say `you should not define methods on this
GF', or `if you define methods on this you have to do x y z too' (for
instance, if you redefine the ordering predicate you better redefine
the equality one too).

I suppose sealing is some of the answer to this.  Java/C++ people also
probably have 50 prepackaged answers which all turn out, on closer
inspection, to be inane.

--tim