1#lang scribble/manual
2@(require "mz.rkt")
3
4
5@title{Equality}
6
7
8Equality is the concept of whether two values are ``the same.'' Racket supports
9a few different kinds of equality by default, though @racket[equal?] is
10preferred for most use cases.
11
12@defproc[(equal? [v1 any/c] [v2 any/c]) boolean?]{
13
14 Two values are @racket[equal?] if and only if they are @racket[eqv?],
15 unless otherwise specified for a particular datatype.
16
17 Datatypes with further specification of @racket[equal?] include
18 strings, byte strings, pairs, mutable pairs, vectors, boxes, hash
19 tables, and inspectable structures. In the last six cases, equality
20 is recursively defined; if both @racket[v1] and @racket[v2] contain
21 reference cycles, they are equal when the infinite unfoldings of the
22 values would be equal. See also @racket[gen:equal+hash] and
23 @racket[prop:impersonator-of].
24
25 @(examples
26   (equal? 'yes 'yes)
27   (equal? 'yes 'no)
28   (equal? (* 6 7) 42)
29   (equal? (expt 2 100) (expt 2 100))
30   (equal? 2 2.0)
31   (let ([v (mcons 1 2)]) (equal? v v))
32   (equal? (mcons 1 2) (mcons 1 2))
33   (equal? (integer->char 955) (integer->char 955))
34   (equal? (make-string 3 #\z) (make-string 3 #\z))
35   (equal? #t #t))}
36
37
38@defproc[(eqv? [v1 any/c] [v2 any/c]) boolean?]{
39
40 Two values are @racket[eqv?] if and only if they are @racket[eq?],
41 unless otherwise specified for a particular datatype.
42
43 The @tech{number} and @tech{character} datatypes are the only ones for which
44 @racket[eqv?] differs from @racket[eq?]. Two numbers are @racket[eqv?] when
45 they have the same exactness, precision, and are both equal and non-zero, both
46 @racketvalfont{+0.0}, both @racketvalfont{+0.0f0}, both @racketvalfont{-0.0},
47 both @racketvalfont{-0.0f0}, both @racketvalfont{+nan.0}, or both
48 @racketvalfont{+nan.f}---considering real and imaginary components separately
49 in the case of @tech{complex numbers}. Two characters are @racket[eqv?] when
50 their @racket[char->integer] results are equal.
51
52 Generally, @racket[eqv?] is identical to @racket[equal?] except that the former
53 cannot recursively compare the contents of compound data types (such as lists
54 and structs) and cannot be customized by user-defined data types. The use of
55 @racket[eqv?] is lightly discouraged in favor of @racket[equal?].
56
57 @(examples
58   (eqv? 'yes 'yes)
59   (eqv? 'yes 'no)
60   (eqv? (* 6 7) 42)
61   (eqv? (expt 2 100) (expt 2 100))
62   (eqv? 2 2.0)
63   (let ([v (mcons 1 2)]) (eqv? v v))
64   (eqv? (mcons 1 2) (mcons 1 2))
65   (eqv? (integer->char 955) (integer->char 955))
66   (eqv? (make-string 3 #\z) (make-string 3 #\z))
67   (eqv? #t #t))}
68
69
70@defproc[(eq? [v1 any/c] [v2 any/c]) boolean?]{
71
72 Return @racket[#t] if @racket[v1] and @racket[v2] refer to the same
73 object, @racket[#f] otherwise. As a special case among @tech{numbers},
74 two @tech{fixnums} that are @racket[=] are also the same according
75 to @racket[eq?]. See also @secref["model-eq"].
76
77 @(examples
78   (eq? 'yes 'yes)
79   (eq? 'yes 'no)
80   (eq? (* 6 7) 42)
81   (eq? (expt 2 100) (expt 2 100))
82   (eq? 2 2.0)
83   (let ([v (mcons 1 2)]) (eq? v v))
84   (eq? (mcons 1 2) (mcons 1 2))
85   (eq? (integer->char 955) (integer->char 955))
86   (eq? (make-string 3 #\z) (make-string 3 #\z))
87   (eq? #t #t))}
88
89
90@defproc[
91 (equal?/recur [v1 any/c] [v2 any/c] [recur-proc (any/c any/c -> any/c)])
92 boolean?]{
93
94 Like @racket[equal?], but using @racket[recur-proc] for recursive
95 comparisons (which means that reference cycles are not handled
96 automatically). Non-@racket[#f] results from @racket[recur-proc] are
97 converted to @racket[#t] before being returned by
98 @racket[equal?/recur].
99
100 @(examples
101   (equal?/recur 1 1 (lambda (a b) #f))
102   (equal?/recur '(1) '(1) (lambda (a b) #f))
103   (equal?/recur '#(1 1 1) '#(1 1.2 3/4)
104                 (lambda (a b) (<= (abs (- a b)) 0.25))))}
105
106
107@section[#:tag "model-eq"]{Object Identity and Comparisons}
108
109
110The @racket[eq?] operator compares two @tech{values}, returning
111@racket[#t] when the values refer to the same @tech{object}. This form
112of equality is suitable for comparing objects that support imperative
113update (e.g., to determine that the effect of modifying an object
114through one reference is visible through another reference). Also, an
115@racket[eq?] test evaluates quickly, and @racket[eq?]-based hashing
116is more lightweight than @racket[equal?]-based hashing in hash tables.
117
118In some cases, however, @racket[eq?] is unsuitable as a comparison
119operator, because the generation of @tech{objects} is not clearly
120defined. In particular, two applications of @racket[+] to the same two
121exact integers may or may not produce results that are @racket[eq?],
122although the results are always @racket[equal?]. Similarly, evaluation
123of a @racket[lambda] form typically generates a new procedure
124@tech{object}, but it may re-use a procedure @tech{object} previously
125generated by the same source @racket[lambda] form.
126
127The behavior of a datatype with respect to @racket[eq?] is generally
128specified with the datatype and its associated procedures.
129
130
131@section{Equality and Hashing}
132
133
134All comparable values have at least one @deftech{hash code} --- an arbitrary
135integer (more specifically a @tech{fixnum}) computed by applying a hash function
136to the value. The defining property of these hash codes is that @bold{equal
137 values have equal hash codes}. Note that the reverse is not true: two unequal
138values can still have equal hash codes. Hash codes are useful for various
139indexing and comparison operations, especially in the implementation of
140@tech{hash tables}. See @secref["hashtables"] for more information.
141
142
143@defproc[(equal-hash-code [v any/c]) fixnum?]{
144
145 Returns a @tech{hash code} consistent with @racket[equal?]. For any two calls
146 with @racket[equal?] values, the returned number is the same. A hash code is
147 computed even when @racket[v] contains a cycle through pairs, vectors, boxes,
148 and/or inspectable structure fields. Additionally, user-defined data types can
149 customize how this hash code is computed by implementing
150 @racket[gen:equal+hash].
151
152 For any @racket[v] that could be produced by @racket[read], if @racket[v2] is
153 produced by @racket[read] for the same input characters, the
154 @racket[(equal-hash-code v)] is the same as @racket[(equal-hash-code v2)] ---
155 even if @racket[v] and @racket[v2] do not exist at the same time (and therefore
156 could not be compared by calling @racket[equal?]).
157
158 @history[
159 #:changed "6.4.0.12"
160 @elem{Strengthened guarantee for @racket[read]able values.}]}
161
162
163@defproc[(equal-secondary-hash-code [v any/c]) fixnum?]{
164
165 Like @racket[equal-hash-code], but computes a secondary @tech{hash code}
166 suitable for use in double hashing.}
167
168
169@defproc[(eq-hash-code [v any/c]) fixnum?]{
170
171 Returns a @tech{hash code} consistent with @racket[eq?]. For any two calls with
172 @racket[eq?] values, the returned number is the same.
173
174 @margin-note{Equal @tech{fixnums} are always @racket[eq?].}}
175
176
177@defproc[(eqv-hash-code [v any/c]) fixnum?]{
178
179 Returns a @tech{hash code} consistent with @racket[eqv?]. For any two calls
180 with @racket[eqv?] values, the returned number is the same.}
181
182
183@section{Implementing Equality for Custom Types}
184
185
186@defthing[gen:equal+hash any/c]{
187 A @tech{generic interface} (see @secref["struct-generics"]) for types that can
188 be compared for equality using @racket[equal?]. The following methods must be
189 implemented:
190
191 @itemize[
192
193 @item{@racket[_equal-proc :
194               (any/c any/c (any/c any/c . -> . boolean?)  . -> . any/c)] ---
195   tests whether the first two arguments are equal, where both values are
196   instances of the structure type to which the generic interface is associated
197   (or a subtype of the structure type).
198
199   The third argument is an @racket[equal?]  predicate to use for
200   recursive equality checks; use the given predicate instead of
201   @racket[equal?] to ensure that data cycles are handled
202   properly and to work with @racket[equal?/recur] (but beware
203   that an arbitrary function can be provided to
204   @racket[equal?/recur] for recursive checks, which means that
205   arguments provided to the predicate might be exposed to
206   arbitrary code).
207
208   The @racket[_equal-proc] is called for a pair of structures
209   only when they are not @racket[eq?], and only when they both
210   have a @racket[gen:equal+hash] value inherited from the same
211   structure type. With this strategy, the order in which
212   @racket[equal?] receives two structures does not matter. It
213   also means that, by default, a structure sub-type inherits the
214   equality predicate of its parent, if any.}
215
216 @item{@racket[_hash-proc :
217               (any/c (any/c . -> . exact-integer?) . -> . exact-integer?)] ---
218   computes a hash code for the given structure, like @racket[equal-hash-code].
219   The first argument is an instance of the structure type (or one of its
220   subtypes) to which the generic interface is associated.
221
222   The second argument is an @racket[equal-hash-code]-like procedure to use for
223   recursive hash-code computation; use the given procedure instead of
224   @racket[equal-hash-code] to ensure that data cycles are handled properly.
225
226   Although the result of @racket[_hash-proc] can be any exact
227   integer, it will be truncated for most purposes to a @tech{fixnum}
228   (e.g., for the result of @racket[equal-hash-code]). Roughly,
229   truncation uses @racket[bitwise-and] to take the lower bits of the
230   number. Thus, variation in the hash-code computation should be
231   reflected in the fixnum-compatible bits of @racket[_hash-proc]'s
232   result. Consumers of a hash code are expected to use variation
233   within the fixnum range appropriately, and producers are @emph{not}
234   responsible to reflect variation in hash codes across the full
235   range of bits that fit within a fixnum.}
236
237 @item{@racket[_hash2-proc :
238               (any/c (any/c . -> . exact-integer?) . -> . exact-integer?)] ---
239   computes a secondary hash code for the given structure. This procedure is
240   like @racket[_hash-proc], but analogous to
241   @racket[equal-secondary-hash-code].}]
242
243 Take care to ensure that @racket[_hash-proc] and @racket[_hash2-proc]
244 are consistent with @racket[_equal-proc]. Specifically,
245 @racket[_hash-proc] and @racket[_hash2-proc] should produce the same
246 value for any two structures for which @racket[_equal-proc] produces a
247 true value.
248
249 When a structure type has no @racket[gen:equal+hash] implementation, then
250 transparent structures (i.e., structures with an @tech{inspector} that
251 is controlled by the current @tech{inspector}) are @racket[equal?]
252 when they are instances of the same structure type (not counting
253 sub-types), and when they have @racket[equal?] field values.  For
254 transparent structures, @racket[equal-hash-code] and
255 @racket[equal-secondary-hash-code] derive hash code using the field
256 values. For opaque structure types, @racket[equal?] is the same as
257 @racket[eq?], and @racket[equal-hash-code] and
258 @racket[equal-secondary-hash-code] results are based only on
259 @racket[eq-hash-code]. If a structure has a @racket[prop:impersonator-of]
260 property, then the @racket[prop:impersonator-of] property takes precedence over
261 @racket[gen:equal+hash] if the property value's procedure returns a
262 non-@racket[#f] value when applied to the structure.
263
264 @(examples
265   (eval:no-prompt
266    (define (farm=? farm1 farm2 recursive-equal?)
267      (and (= (farm-apples farm1)
268              (farm-apples farm2))
269           (= (farm-oranges farm1)
270              (farm-oranges farm2))
271           (= (farm-sheep farm1)
272              (farm-sheep farm2))))
273
274    (define (farm-hash-code farm recursive-equal-hash)
275      (+ (* 10000 (farm-apples farm))
276         (* 100 (farm-oranges farm))
277         (* 1 (farm-sheep farm))))
278
279    (define (farm-secondary-hash-code farm recursive-equal-hash)
280      (+ (* 10000 (farm-sheep farm))
281         (* 100 (farm-apples farm))
282         (* 1 (farm-oranges farm))))
283
284    (struct farm (apples oranges sheep)
285      #:methods gen:equal+hash
286      [(define equal-proc farm=?)
287       (define hash-proc  farm-hash-code)
288       (define hash2-proc farm-secondary-hash-code)])
289
290    (define eastern-farm (farm 5 2 20))
291    (define western-farm (farm 18 6 14))
292    (define northern-farm (farm 5 20 20))
293    (define southern-farm (farm 18 6 14)))
294
295   (equal? eastern-farm western-farm)
296   (equal? eastern-farm northern-farm)
297   (equal? western-farm southern-farm))}
298
299
300@defthing[prop:equal+hash struct-type-property?]{
301
302 A @tech{structure type property} (see @secref["structprops"])
303 that supplies an equality predicate and hashing functions for a structure
304 type. Using the @racket[prop:equal+hash] property is discouraged; the
305 @racket[gen:equal+hash] @tech{generic interface} should be used instead.
306 A @racket[prop:equal+hash] property value is a list of three procedures
307 that correspond to the methods of @racket[gen:equal+hash]:
308
309 @itemize[
310 @item{@racket[_equal-proc :
311               (any/c any/c (any/c any/c . -> . boolean?)  . -> . any/c)]}
312
313 @item{@racket[_hash-proc :
314               (any/c (any/c . -> . exact-integer?) . -> . exact-integer?)]}
315
316 @item{@racket[_hash2-proc :
317               (any/c (any/c . -> . exact-integer?) . -> . exact-integer?)]}]}
318