1#lang scribble/doc
2@(require "mz.rkt"
3          racket/class
4          (for-syntax racket/base racket/serialize racket/trait)
5          (for-label racket/serialize))
6
7@(begin
8
9(define-syntax sees
10  (syntax-rules ()
11    [(_) ""]
12    [(_ s) (elem " and " (secref s))]
13    [(_ s ... s0) (elem (elem ", " (secref s)) ... ", and " (secref s0))]))
14
15(define-syntax (defclassforms stx)
16  (syntax-case stx (*)
17    [(_ [* (form ...) (also ...) more ...])
18     #'(defform* (form  ...)
19         "See " @racket[class*] (sees also ...) "; use"
20         " outside the body of a " @racket[class*] " form is a syntax error."
21         more ...)]
22    [(_ [form (also ...) more ...])
23     #'(defclassforms [* (form) (also ...) more ...])]
24    [(_ form ...)
25     #'(begin (defclassforms form) ...)]))
26
27(define-syntax (defstarshorthands stx)
28  (syntax-case stx ()
29    [(_ form)
30     (with-syntax ([name (string->symbol
31                           (let ([s (symbol->string (syntax-e #'form))])
32                             (substring s 0 (sub1 (string-length s)))))]
33                   [tmpl (let ([s #'(... (thing (id expr) ...))])
34                           (datum->syntax s
35                                          (cons (datum->syntax
36                                                 #'form
37                                                 (syntax-e #'form)
38                                                 (car (syntax-e s)))
39                                                (cdr (syntax-e s)))
40                                          s))])
41       #'(...
42          (defform tmpl
43            "Shorthand for " (racket (begin (#,(racket name) id) ... (define id _expr) ...)) ".")))]
44     [(_ form ...)
45      #'(begin (defstarshorthands form) ...)]))
46
47(define-syntax (defdefshorthands stx)
48  (syntax-case stx ()
49    [(_ form)
50     (with-syntax ([name (string->symbol
51                          (let ([s (symbol->string (syntax-e #'form))])
52                            (string-append "define/" s)))])
53       (with-syntax ([tmpl1 (let ([s #'(define id expr)])
54                              (datum->syntax s
55                                             (cons (datum->syntax
56                                                    #'form
57                                                    (syntax-e #'name)
58                                                    (car (syntax-e s)))
59                                                   (cdr (syntax-e s)))
60                                             s))])
61         #'(...
62            (defform* [tmpl1 (#,(racket name) (id . formals) body ...+)]
63              "Shorthand for "
64              (racket (begin (#,(racket form) id) (define id expr)))
65              " or "
66              (racket (begin (#,(racket form) id) (define (id . formals) body ...+)))))))]
67     [(_ form ...)
68      #'(begin (defdefshorthands form) ...)]))
69
70(define class-eval (make-base-eval))
71(define class-ctc-eval (make-base-eval))
72
73)
74
75@examples[#:hidden #:eval class-eval
76          (require racket/class racket/contract)]
77@examples[#:hidden #:eval class-ctc-eval
78          (require racket/class racket/contract)]
79
80@title[#:tag "mzlib:class" #:style 'toc]{Classes and Objects}
81
82@guideintro["classes"]{classes and objects}
83
84@note-lib[racket/class #:use-sources (racket/private/class-internal)]
85
86A @deftech{class} specifies
87
88@itemize[
89
90 @item{a collection of fields;}
91
92 @item{a collection of methods;}
93
94 @item{initial value expressions for the fields;  and}
95
96 @item{initialization variables that are bound to initialization
97 arguments.}
98
99]
100
101In the context of the class system, an @defterm{object} is a
102collection of bindings for fields that are instantiated according to a
103class description.
104
105The class system allows a program to define a new class (a
106@deftech{derived class}) in terms of an existing class (the
107@deftech{superclass}) using inheritance, overriding, and augmenting:
108
109@itemize[
110
111 @item{@deftech{inheritance}: An object of a derived class supports
112 methods and instantiates fields declared by the derived class's
113 superclass, as well as methods and fields declared in the derived
114 class expression.}
115
116 @item{@deftech{overriding}: Some methods declared in a superclass can
117 be replaced in the derived class. References to the overridden method
118 in the superclass use the implementation in the derived class.}
119
120 @item{@deftech{augmenting}: Some methods declared in a superclass can
121 be merely extended in the derived class. The superclass method
122 specifically delegates to the augmenting method in the derived class.}
123
124]
125
126An @deftech{interface} is a collection of method names to be
127implemented by a class, combined with a derivation requirement. A
128class @deftech{implements} an interface when it
129
130@itemize[
131
132 @item{declares (or inherits) a public method for each variable in the
133 interface;}
134
135 @item{is derived from the class required by the interface, if any; and}
136
137 @item{specifically declares its intention to implement the interface.}
138
139]
140
141A class can implement any number of interfaces. A derived class
142automatically implements any interface that its superclass
143implements. Each class also implements an implicitly-defined interface
144that is associated with the class. The implicitly-defined interface
145contains all of the class's public method names, and it requires that
146all other implementations of the interface are derived from the class.
147
148A new interface can @deftech{extend} one or more interfaces with
149additional method names; each class that implements the extended
150interface also implements the original interfaces. The derivation
151requirements of the original interface must be consistent, and the
152extended interface inherits the most specific derivation requirement
153from the original interfaces.
154
155Classes, objects, and interfaces are all values. However, a class or
156interface is not an object (i.e., there are no ``meta-classes'' or
157``meta-interfaces'').
158
159@local-table-of-contents[]
160
161@; ------------------------------------------------------------------------
162
163@section[#:tag "createinterface"]{Creating Interfaces}
164
165@guideintro["classes"]{classes, objects, and interfaces}
166
167@defform/subs[(interface (super-interface-expr ...) name-clause ...)
168              ([name-clause
169                id
170                (id contract-expr)])]{
171
172Produces an interface. The @racket[id]s must be mutually distinct.
173
174Each @racket[super-interface-expr] is evaluated (in order) when the
175@racket[interface] expression is evaluated. The result of each
176@racket[super-interface-expr] must be an interface value, otherwise
177the @exnraise[exn:fail:object].  The interfaces returned by the
178@racket[super-interface-expr]s are the new interface's
179superinterfaces, which are all extended by the new interface. Any
180class that implements the new interface also implements all of the
181superinterfaces.
182
183The result of an @racket[interface] expression is an interface that
184includes all of the specified @racket[id]s, plus all identifiers from
185the superinterfaces. Duplicate identifier names among the
186superinterfaces are ignored, but if a superinterface contains one of
187the @racket[id]s in the @racket[interface] expression, the
188@exnraise[exn:fail:object]. A given @racket[id] may be paired with
189a corresponding @racket[contract-expr].
190
191If no @racket[super-interface-expr]s are provided, then the derivation
192requirement of the resulting interface is trivial: any class that
193implements the interface must be derived from @racket[object%].
194Otherwise, the implementation requirement of the resulting interface
195is the most specific requirement from its superinterfaces. If the
196superinterfaces specify inconsistent derivation requirements, the
197@exnraise[exn:fail:object].
198
199@examples[
200#:eval class-ctc-eval
201#:no-prompt
202(define file-interface<%>
203  (interface () open close read-byte write-byte))
204(define directory-interface<%>
205  (interface (file-interface<%>)
206    [file-list (->m (listof (is-a?/c file-interface<%>)))]
207    parent-directory))
208]}
209
210@defform/subs[(interface* (super-interface-expr ...)
211                          ([property-expr val-expr] ...)
212                name-clause ...)
213              ([name-clause
214                id
215                (id contract-expr)])]{
216
217Like @racket[interface], but also associates to the interface the
218structure-type properties produced by the @racket[property-expr]s with
219the corresponding @racket[val-expr]s.
220
221Whenever the resulting interface (or a sub-interface derived from it)
222is explicitly implemented by a class through the @racket[class*] form,
223each property is attached with its value to a structure type that
224instantiated by instances of the class. Specifically, the property is
225attached to a structure type with zero immediate fields, which is
226extended to produce the internal structure type for instances of the
227class (so that no information about fields is accessible to the
228structure type property's guard, if any).
229
230@examples[
231#:eval class-eval
232#:no-prompt
233(define i<%> (interface* () ([prop:custom-write
234                              (lambda (obj port mode) (void))])
235               method1 method2 method3))
236]}
237
238@; ------------------------------------------------------------------------
239
240@section[#:tag "createclass"]{Creating Classes}
241
242@guideintro["classes"]{classes and objects}
243
244@defthing[object% class?]{
245
246A built-in class that has no methods fields, implements only its own
247interface @racket[(class->interface object%)], and is transparent
248(i.e,. its inspector is @racket[#f], so all immediate instances are
249@racket[equal?]). All other classes are derived from @racket[object%].}
250
251
252@defform/subs[
253#:literals (inspect init init-field field inherit-field init-rest init-rest
254            public pubment public-final override override-final overment augment augride
255            augment-final private abstract inherit inherit/super inherit/inner
256            rename-super rename-inner begin lambda case-lambda let-values letrec-values
257            define-values #%plain-lambda chaperone-procedure)
258(class* superclass-expr (interface-expr ...)
259  class-clause
260  ...)
261([class-clause
262  (inspect inspector-expr)
263  (init init-decl ...)
264  (init-field init-decl ...)
265  (field field-decl ...)
266  (inherit-field maybe-renamed ...)
267  (init-rest id)
268  (init-rest)
269  (public maybe-renamed ...)
270  (pubment maybe-renamed ...)
271  (public-final maybe-renamed ...)
272  (override maybe-renamed ...)
273  (overment maybe-renamed ...)
274  (override-final maybe-renamed ...)
275  (augment maybe-renamed ...)
276  (augride maybe-renamed ...)
277  (augment-final maybe-renamed ...)
278  (private id ...)
279  (abstract id ...)
280  (inherit maybe-renamed ...)
281  (inherit/super maybe-renamed ...)
282  (inherit/inner maybe-renamed ...)
283  (rename-super renamed ...)
284  (rename-inner renamed ...)
285  method-definition
286  definition
287  expr
288  (begin class-clause ...)]
289
290[init-decl
291  id
292  (renamed)
293  (maybe-renamed default-value-expr)]
294
295[field-decl
296  (maybe-renamed default-value-expr)]
297
298[maybe-renamed
299  id
300  renamed]
301
302[renamed
303  (internal-id external-id)]
304
305[method-definition
306  (define-values (id) method-procedure)]
307
308[method-procedure
309  (lambda kw-formals expr ...+)
310  (case-lambda (formals expr ...+) ...)
311  (#%plain-lambda formals expr ...+)
312  (let-values ([(id) method-procedure] ...)
313    method-procedure)
314  (letrec-values ([(id) method-procedure] ...)
315    method-procedure)
316  (let-values ([(id) method-procedure] ...+)
317    id)
318  (letrec-values ([(id) method-procedure] ...+)
319    id)
320  (chaperone-procedure method-procedure wrapper-proc
321                       other-arg-expr ...)])]{
322
323Produces a class value.
324
325The @racket[superclass-expr] expression is evaluated when the
326@racket[class*] expression is evaluated. The result must be a class
327value (possibly @racket[object%]), otherwise the
328@exnraise[exn:fail:object].  The result of the
329@racket[superclass-expr] expression is the new class's superclass.
330
331The @racket[interface-expr] expressions are also evaluated when the
332@racket[class*] expression is evaluated, after
333@racket[superclass-expr] is evaluated. The result of each
334@racket[interface-expr] must be an interface value, otherwise the
335@exnraise[exn:fail:object].  The interfaces returned by the
336@racket[interface-expr]s are all implemented by the class. For each
337identifier in each interface, the class (or one of its ancestors) must
338declare a public method with the same name, otherwise the
339@exnraise[exn:fail:object]. The class's superclass must satisfy the
340implementation requirement of each interface, otherwise the
341@exnraise[exn:fail:object].
342
343An @racket[inspect] @racket[class-clause] selects an inspector (see
344@secref["inspectors"]) for the class extension. The
345@racket[inspector-expr] must evaluate to an inspector or @racket[#f]
346when the @racket[class*] form is evaluated. Just as for structure
347types, an inspector controls access to the class's fields, including
348private fields, and also affects comparisons using @racket[equal?]. If
349no @racket[inspect] clause is provided, access to the class is
350controlled by the parent of the current inspector (see
351@secref["inspectors"]). A syntax error is reported if more than one
352@racket[inspect] clause is specified.
353
354The other @racket[class-clause]s define initialization arguments,
355public and private fields, and public and private methods. For each
356@racket[id] or @racket[maybe-renamed] in a @racket[public],
357@racket[override], @racket[augment], @racket[pubment],
358@racket[overment], @racket[augride], @racket[public-final],
359@racket[override-final], @racket[augment-final], or @racket[private]
360clause, there must be one @racket[method-definition]. All other
361definition @racket[class-clause]s create private fields. All remaining
362@racket[expr]s are initialization expressions to be evaluated when the
363class is instantiated (see @secref["objcreation"]).
364
365The result of a @racket[class*] expression is a new class, derived
366from the specified superclass and implementing the specified
367interfaces. Instances of the class are created with the
368@racket[instantiate] form or @racket[make-object] procedure, as
369described in @secref["objcreation"].
370
371Each @racket[class-clause] is (partially) macro-expanded to reveal its
372shapes. If a @racket[class-clause] is a @racket[begin] expression, its
373sub-expressions are lifted out of the @racket[begin] and treated as
374@racket[class-clause]s, in the same way that @racket[begin] is
375flattened for top-level and embedded definitions.
376
377Within a @racket[class*] form for instances of the new class,
378@racket[this] is bound to the object itself;
379@racket[this%] is bound to the class of the object;
380@racket[super-instantiate], @racket[super-make-object], and
381@racket[super-new] are bound to forms to initialize fields in the
382superclass (see @secref["objcreation"]); @racket[super] is
383available for calling superclass methods (see
384@secref["clmethoddefs"]); and @racket[inner] is available for
385calling subclass augmentations of methods (see
386@secref["clmethoddefs"]).}
387
388@defform[(class superclass-expr class-clause ...)]{
389
390Like @racket[class*], but omits the @racket[_interface-expr]s, for the case that none are needed.
391
392@examples[
393#:eval class-eval
394#:no-prompt
395(define book-class%
396  (class object%
397    (field (pages 5))
398    (define/public (letters)
399      (* pages 500))
400    (super-new)))
401]}
402
403@defidform[this]{
404
405@index['("self")]{Within} a @racket[class*] form, @racket[this] refers
406to the current object (i.e., the object being initialized or whose
407method was called). Use outside the body of a @racket[class*] form is
408a syntax error.
409
410@examples[
411#:eval class-eval
412(eval:no-prompt
413 (define (describe obj)
414   (printf "Hello ~a\n" obj))
415 (define table%
416   (class object%
417     (define/public (describe-self)
418       (describe this))
419     (super-new))))
420(send (new table%) describe-self)
421]}
422
423@defidform[this%]{
424
425Within a @racket[class*] form, @racket[this%] refers to the class
426of the current object (i.e., the object being initialized or whose
427method was called).  Use outside the body of a @racket[class*] form is
428a syntax error.
429
430@examples[
431#:eval class-eval
432(eval:no-prompt
433 (define account%
434   (class object%
435     (super-new)
436     (init-field balance)
437     (define/public (add n)
438       (new this% [balance (+ n balance)]))))
439 (define savings%
440   (class account%
441     (super-new)
442     (inherit-field balance)
443     (define interest 0.04)
444     (define/public (add-interest)
445       (send this add (* interest balance))))))
446(let* ([acct (new savings% [balance 500])]
447       [acct (send acct add 500)]
448       [acct (send acct add-interest)])
449  (printf "Current balance: ~a\n" (get-field balance acct)))
450]}
451
452@defclassforms[
453  [(inspect inspector-expr) ()]
454  [(init init-decl ...) ("clinitvars")
455   @examples[#:eval class-eval
456     (class object%
457       (super-new)
458       (init turnip
459             [(internal-potato potato)]
460             [carrot 'good]
461             [(internal-rutabaga rutabaga) 'okay]))]]
462  [(init-field init-decl ...) ("clinitvars" "clfields")
463   @examples[#:eval class-eval
464     (class object%
465       (super-new)
466       (init-field turkey
467                   [(internal-ostrich ostrich)]
468                   [chicken 7]
469                   [(internal-emu emu) 13]))]]
470  [(field field-decl ...) ("clfields")
471   @examples[#:eval class-eval
472     (class object%
473       (super-new)
474       (field [minestrone 'ready]
475              [(internal-coq-au-vin coq-au-vin) 'stewing]))]]
476  [(inherit-field maybe-renamed ...) ("clfields")
477   @examples[#:eval class-eval
478     (eval:no-prompt
479      (define cookbook%
480        (class object%
481          (super-new)
482          (field [recipes '(caldo-verde oyakodon eggs-benedict)]
483                 [pages 389]))))
484     (class cookbook%
485       (super-new)
486       (inherit-field recipes
487                      [internal-pages pages]))]]
488  [* ((init-rest id) (init-rest)) ("clinitvars")
489   @examples[#:eval class-eval
490     (eval:no-prompt
491      (define fruit-basket%
492        (class object%
493          (super-new)
494          (init-rest fruits)
495          (displayln fruits))))
496     (make-object fruit-basket% 'kiwi 'lychee 'melon)]]
497  [(public maybe-renamed ...) ("clmethoddefs")
498    @examples[#:eval class-eval
499      (eval:no-prompt
500       (define jumper%
501         (class object%
502           (super-new)
503           (define (skip) 'skip)
504           (define (hop) 'hop)
505           (public skip [hop jump]))))
506      (send (new jumper%) skip)
507      (send (new jumper%) jump)]]
508  [(pubment maybe-renamed ...) ("clmethoddefs")
509    @examples[#:eval class-eval
510      (eval:no-prompt
511       (define runner%
512         (class object%
513           (super-new)
514           (define (run) 'run)
515           (define (trot) 'trot)
516           (pubment run [trot jog]))))
517      (send (new runner%) run)
518      (send (new runner%) jog)]]
519  [(public-final maybe-renamed ...) ("clmethoddefs")
520    @examples[#:eval class-eval
521      (eval:no-prompt
522       (define point%
523         (class object%
524           (super-new)
525           (init-field [x 0] [y 0])
526            (define (get-x) x)
527           (define (do-get-y) y)
528           (public-final get-x [do-get-y get-y]))))
529      (send (new point% [x 1] [y 3]) get-y)
530      (eval:error
531       (class point%
532         (super-new)
533         (define (get-x) 3.14)
534         (override get-x)))]]
535  [(override maybe-renamed ...) ("clmethoddefs")
536    @examples[#:eval class-eval
537      (eval:no-prompt
538       (define sheep%
539         (class object%
540           (super-new)
541           (define/public (bleat)
542             (displayln "baaaaaaaaah")))))
543      (eval:no-prompt
544       (define confused-sheep%
545         (class sheep%
546           (super-new)
547           (define (bleat)
548             (super bleat)
549             (displayln "???"))
550           (override bleat))))
551      (send (new sheep%) bleat)
552      (send (new confused-sheep%) bleat)]]
553  [(overment maybe-renamed ...) ("clmethoddefs")
554    @examples[#:eval class-eval
555      (eval:no-prompt
556       (define turkey%
557         (class object%
558           (super-new)
559           (define/public (gobble)
560             (displayln "gobble gobble")))))
561      (eval:no-prompt
562       (define extra-turkey%
563         (class turkey%
564           (super-new)
565           (define (gobble)
566             (super gobble)
567             (displayln "gobble gobble gobble")
568             (inner (void) gobble))
569           (overment gobble))))
570      (eval:no-prompt
571       (define cyborg-turkey%
572         (class extra-turkey%
573           (super-new)
574           (define/augment (gobble)
575             (displayln "110011111011111100010110001011011001100101")))))
576      (send (new extra-turkey%) gobble)
577      (send (new cyborg-turkey%) gobble)]]
578  [(override-final maybe-renamed ...) ("clmethoddefs")
579    @examples[#:eval class-eval
580      (eval:no-prompt
581       (define meeper%
582         (class object%
583           (super-new)
584           (define/public (meep)
585             (displayln "meep")))))
586      (eval:no-prompt
587       (define final-meeper%
588         (class meeper%
589           (super-new)
590           (define (meep)
591             (super meep)
592             (displayln "This meeping ends with me"))
593           (override-final meep))))
594      (send (new meeper%) meep)
595      (send (new final-meeper%) meep)]]
596  [(augment maybe-renamed ...) ("clmethoddefs")
597    @examples[#:eval class-eval
598      (eval:no-prompt
599       (define buzzer%
600         (class object%
601           (super-new)
602           (define/pubment (buzz)
603             (displayln "bzzzt")
604             (inner (void) buzz)))))
605      (eval:no-prompt
606       (define loud-buzzer%
607         (class buzzer%
608           (super-new)
609           (define (buzz)
610             (displayln "BZZZZZZZZZT"))
611           (augment buzz))))
612      (send (new buzzer%) buzz)
613      (send (new loud-buzzer%) buzz)]]
614  [(augride maybe-renamed ...) ("clmethoddefs")]
615  [(augment-final maybe-renamed ...) ("clmethoddefs")]
616  [(private id ...) ("clmethoddefs")
617    @examples[#:eval class-eval
618      (eval:no-prompt
619       (define light%
620         (class object%
621           (super-new)
622           (define on? #t)
623           (define (toggle) (set! on? (not on?)))
624           (private toggle)
625           (define (flick) (toggle))
626           (public flick))))
627      (eval:error (send (new light%) toggle))
628      (send (new light%) flick)]]
629  [(abstract id ...) ("clmethoddefs")
630    @examples[#:eval class-eval
631      (eval:no-prompt
632       (define train%
633         (class object%
634           (super-new)
635           (abstract get-speed)
636           (init-field [position 0])
637           (define/public (move)
638             (new this% [position (+ position (get-speed))])))))
639      (eval:no-prompt
640       (define acela%
641         (class train%
642           (super-new)
643           (define/override (get-speed) 241))))
644      (eval:no-prompt
645       (define talgo-350%
646         (class train%
647           (super-new)
648           (define/override (get-speed) 330))))
649      (eval:error (new train%))
650      (send (new acela%) move)]]
651  [(inherit maybe-renamed ...) ("classinherit")
652    @examples[#:eval class-eval
653      (eval:no-prompt
654       (define alarm%
655         (class object%
656           (super-new)
657           (define/public (alarm)
658             (displayln "beeeeeeeep")))))
659      (eval:no-prompt
660       (define car-alarm%
661         (class alarm%
662           (super-new)
663           (init-field proximity)
664           (inherit alarm)
665           (when (< proximity 10)
666             (alarm)))))
667      (new car-alarm% [proximity 5])]]
668  [(inherit/super maybe-renamed ...)  ("classinherit")]
669  [(inherit/inner maybe-renamed ...) ("classinherit")]
670  [(rename-super renamed ...) ("classinherit")]
671  [(rename-inner renamed ...) ("classinherit")]
672]
673
674@defstarshorthands[
675 public*
676 pubment*
677 public-final*
678 override*
679 overment*
680 override-final*
681 augment*
682 augride*
683 augment-final*
684 private*
685]
686
687@defdefshorthands[
688 public pubment public-final override
689 overment override-final augment augride
690 augment-final private
691]
692
693
694@defform[
695(class/derived original-datum
696  (name-id super-expr (interface-expr ...) deserialize-id-expr)
697  class-clause
698  ...)
699]{
700
701Like @racket[class*], but includes a sub-expression to be used as the
702source for all syntax errors within the class definition. For example,
703@racket[define-serializable-class] expands to @racket[class/derived]
704so that errors in the body of the class are reported in terms of
705@racket[define-serializable-class] instead of @racket[class].
706
707The @racket[original-datum] is the original expression to use for
708reporting errors.
709
710The @racket[name-id] is used to name the resulting class; if it
711is @racket[#f], the class name is inferred.
712
713The @racket[super-expr], @racket[interface-expr]s, and
714@racket[class-clause]s are as for @racket[class*].
715
716If the @racket[deserialize-id-expr] is not literally @racket[#f], then
717a serializable class is generated, and the result is two values
718instead of one: the class and a deserialize-info structure produced by
719@racket[make-deserialize-info]. The @racket[deserialize-id-expr]
720should produce a value suitable as the second argument to
721@racket[make-serialize-info], and it should refer to an export whose
722value is the deserialize-info structure.
723
724Future optional forms may be added to the sequence that currently ends
725with @racket[deserialize-id-expr].}
726
727@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
728
729@subsection[#:tag "clinitvars"]{Initialization Variables}
730
731A class's initialization variables, declared with @racket[init],
732@racket[init-field], and @racket[init-rest], are instantiated
733for each object of a class. Initialization variables can be used in
734the initial value expressions of fields, default value expressions
735for initialization arguments, and in initialization expressions.  Only
736initialization variables declared with @racket[init-field] can be
737accessed from methods; accessing any other initialization variable
738from a method is a syntax error.
739
740The values bound to initialization variables are
741
742@itemize[
743
744 @item{the arguments provided with @racket[instantiate] or passed to
745 @racket[make-object], if the object is created as a direct instance
746 of the class; or,}
747
748 @item{the arguments passed to the superclass initialization form or
749 procedure, if the object is created as an instance of a derived
750 class.}
751
752]
753
754If an initialization argument is not provided for an initialization
755variable that has an associated @racket[_default-value-expr], then the
756@racket[_default-value-expr] expression is evaluated to obtain a value
757for the variable. A @racket[_default-value-expr] is only evaluated when
758an argument is not provided for its variable. The environment of
759@racket[_default-value-expr] includes all of the initialization
760variables, all of the fields, and all of the methods of the class. If
761multiple @racket[_default-value-expr]s are evaluated, they are
762evaluated from left to right. Object creation and field initialization
763are described in detail in @secref["objcreation"].
764
765If an initialization variable has no @racket[_default-value-expr], then
766the object creation or superclass initialization call must supply an
767argument for the variable, otherwise the @exnraise[exn:fail:object].
768
769Initialization arguments can be provided by name or by position.  The
770external name of an initialization variable can be used with
771@racket[instantiate] or with the superclass initialization form. Those
772forms also accept by-position arguments. The @racket[make-object]
773procedure and the superclass initialization procedure accept only
774by-position arguments.
775
776Arguments provided by position are converted into by-name arguments
777using the order of @racket[init] and @racket[init-field] clauses and
778the order of variables within each clause. When an @racket[instantiate]
779form provides both by-position and by-name arguments, the converted
780arguments are placed before by-name arguments. (The order can be
781significant; see also @secref["objcreation"].)
782
783Unless a class contains an @racket[init-rest] clause, when the number
784of by-position arguments exceeds the number of declared initialization
785variables, the order of variables in the superclass (and so on, up the
786superclass chain) determines the by-name conversion.
787
788If a class expression contains an @racket[init-rest] clause, there
789must be only one, and it must be last. If it declares a variable, then
790the variable receives extra by-position initialization arguments as a
791list (similar to a dotted ``rest argument'' in a procedure).  An
792@racket[init-rest] variable can receive by-position initialization
793arguments that are left over from a by-name conversion for a derived
794class. When a derived class's superclass initialization provides even
795more by-position arguments, they are prefixed onto the by-position
796arguments accumulated so far.
797
798If too few or too many by-position initialization arguments are
799provided to an object creation or superclass initialization, then the
800@exnraise[exn:fail:object]. Similarly, if extra by-position arguments
801are provided to a class with an @racket[init-rest] clause, the
802@exnraise[exn:fail:object].
803
804Unused (by-name) arguments are to be propagated to the superclass, as
805described in @secref["objcreation"].  Multiple initialization
806arguments can use the same name if the class derivation contains
807multiple declarations (in different classes) of initialization
808variables with the name. See @secref["objcreation"] for further
809details.
810
811See also @secref["extnames"] for information about internal and
812external names.
813
814@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
815
816@subsection[#:tag "clfields"]{Fields}
817
818Each @racket[field], @racket[init-field], and non-method
819@racket[define-values] clause in a class declares one or more new
820fields for the class. Fields declared with @racket[field] or
821@racket[init-field] are public. Public fields can be accessed and
822mutated by subclasses using @racket[inherit-field]. Public fields are
823also accessible outside the class via @racket[class-field-accessor]
824and mutable via @racket[class-field-mutator] (see
825@secref["ivaraccess"]). Fields declared with @racket[define-values]
826are accessible only within the class.
827
828A field declared with @racket[init-field] is both a public field and
829an initialization variable. See @secref["clinitvars"] for
830information about initialization variables.
831
832An @racket[inherit-field] declaration makes a public field defined by
833a superclass directly accessible in the class expression. If the
834indicated field is not defined in the superclass, the
835@exnraise[exn:fail:object] when the class expression is evaluated.
836Every field in a superclass is present in a derived class, even if it
837is not declared with @racket[inherit-field] in the derived class. The
838@racket[inherit-field] clause does not control inheritance, but merely
839controls lexical scope within a class expression.
840
841When an object is first created, all of its fields have the
842@|undefined-const| value (see @secref["void"]). The fields of a
843class are initialized at the same time that the class's initialization
844expressions are evaluated; see @secref["objcreation"] for more
845information.
846
847See also @secref["extnames"] for information about internal and
848external names.
849
850@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
851
852@subsection[#:tag "clmethods"]{Methods}
853
854@subsubsection[#:tag "clmethoddefs"]{Method Definitions}
855
856Each @racket[public], @racket[override], @racket[augment],
857@racket[pubment], @racket[overment], @racket[augride],
858@racket[public-final], @racket[override-final],
859@racket[augment-final], and @racket[private]
860clause in a class declares one or more method names. Each method name
861must have a corresponding @racket[_method-definition]. The order of
862@racket[public], @|etc|, clauses and their corresponding definitions
863(among themselves, and with respect to other clauses in the class)
864does not matter.
865
866As shown in the grammar for @racket[class*], a method definition is
867syntactically restricted to certain procedure forms, as defined by the
868grammar for @racket[_method-procedure]; in the last two forms of
869@racket[_method-procedure], the body @racket[id] must be one of the
870@racket[id]s bound by @racket[let-values] or @racket[letrec-values]. A
871@racket[_method-procedure] expression is not evaluated
872directly. Instead, for each method, a class-specific method procedure
873is created; it takes an initial object argument, in addition to the
874arguments the procedure would accept if the @racket[_method-procedure]
875expression were evaluated directly. The body of the procedure is
876transformed to access methods and fields through the object argument.
877
878A method declared with @racket[public], @racket[pubment], or
879@racket[public-final] introduces a new method into a class. The method
880must not be present already in the superclass, otherwise the
881@exnraise[exn:fail:object] when the class expression is evaluated. A
882method declared with @racket[public] can be overridden in a subclass
883that uses @racket[override], @racket[overment], or
884@racket[override-final].  A method declared with @racket[pubment] can
885be augmented in a subclass that uses @racket[augment],
886@racket[augride], or @racket[augment-final]. A method declared with
887@racket[public-final] cannot be overridden or augmented in a subclass.
888
889A method declared with @racket[override], @racket[overment], or
890@racket[override-final] overrides a definition already present in the
891superclass. If the method is not already present, the
892@exnraise[exn:fail:object] when the class expression is evaluated.  A
893method declared with @racket[override] can be overridden again in a
894subclass that uses @racket[override], @racket[overment], or
895@racket[override-final].  A method declared with @racket[overment] can
896be augmented in a subclass that uses @racket[augment],
897@racket[augride], or @racket[augment-final]. A method declared with
898@racket[override-final] cannot be overridden further or augmented in a
899subclass.
900
901A method declared with @racket[augment], @racket[augride], or
902@racket[augment-final] augments a definition already present in the
903superclass. If the method is not already present, the
904@exnraise[exn:fail:object] when the class expression is evaluated.  A
905method declared with @racket[augment] can be augmented further in a
906subclass that uses @racket[augment], @racket[augride], or
907@racket[augment-final]. A method declared with @racket[augride] can be
908overridden in a subclass that uses @racket[override],
909@racket[overment], or @racket[override-final]. (Such an override
910merely replaces the augmentation, not the method that is augmented.)
911A method declared with @racket[augment-final] cannot be overridden or
912augmented further in a subclass.
913
914A method declared with @racket[private] is not accessible outside the
915class expression, cannot be overridden, and never overrides a method
916in the superclass.
917
918When a method is declared with @racket[override], @racket[overment],
919or @racket[override-final], then the superclass implementation of the
920method can be called using @racket[super] form.
921
922When a method is declared with @racket[pubment], @racket[augment], or
923@racket[overment], then a subclass augmenting method can be called
924using the @racket[inner] form. The only difference between
925@racket[public-final] and @racket[pubment] without a corresponding
926@racket[inner] is that @racket[public-final] prevents the declaration
927of augmenting methods that would be ignored.
928
929A method declared with @racket[abstract] must be declared without
930an implementation. Subclasses may implement abstract methods via the
931@racket[override], @racket[overment], or @racket[override-final]
932forms. Any class that contains or inherits any abstract methods is
933considered abstract and cannot be instantiated.
934
935@defform*[[(super id arg ...)
936           (super id arg ... . arg-list-expr)]]{
937
938Always accesses the superclass method, independent of whether the
939method is overridden again in subclasses. Using the @racket[super]
940form outside of @racket[class*] is a syntax error. Each @racket[arg]
941is as for @racket[#%app]: either @racket[_arg-expr] or
942@racket[_keyword _arg-expr].
943
944The second form is analogous to using @racket[apply] with a procedure;
945the @racket[arg-list-expr] must not be a parenthesized expression.}
946
947@defform*[[(inner default-expr id arg ...)
948           (inner default-expr id arg ... . arg-list-expr)]]{
949
950If the object's class does not supply an augmenting method, then
951@racket[default-expr] is evaluated, and the @racket[arg] expressions
952are not evaluated. Otherwise, the augmenting method is called with the
953@racket[arg] results as arguments, and @racket[default-expr] is not
954evaluated. If no @racket[inner] call is evaluated for a particular
955method, then augmenting methods supplied by subclasses are never
956used. Using the @racket[inner] form outside of @racket[class*] is an
957syntax error.
958
959The second form is analogous to using @racket[apply] with a procedure;
960the @racket[arg-list-expr] must not be a parenthesized expression.}
961
962@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
963
964@subsubsection[#:tag "classinherit"]{Inherited and Superclass Methods}
965
966Each @racket[inherit], @racket[inherit/super], @racket[inherit/inner],
967@racket[rename-super], and @racket[rename-inner] clause declares one
968or more methods that are defined in the class, but must be present in
969the superclass. The @racket[rename-super] and @racket[rename-inner]
970declarations are rarely used, since @racket[inherit/super] and
971@racket[inherit/inner] provide the same access. Also, superclass and
972augmenting methods are typically accessed through @racket[super] and
973@racket[inner] in a class that also declares the methods, instead of
974through @racket[inherit/super], @racket[inherit/inner],
975@racket[rename-super], or @racket[rename-inner].
976
977Method names declared with @racket[inherit], @racket[inherit/super],
978or @racket[inherit/inner] access overriding declarations, if any, at
979run time. Method names declared with @racket[inherit/super] can also
980be used with the @racket[super] form to access the superclass
981implementation, and method names declared with @racket[inherit/inner]
982can also be used with the @racket[inner] form to access an augmenting
983method, if any.
984
985Method names declared with @racket[rename-super] always access the
986superclass's implementation at run-time. Methods declared with
987@racket[rename-inner] access a subclass's augmenting method, if any,
988and must be called with the form
989
990@racketblock[
991(_id (lambda () _default-expr) _arg ...)
992]
993
994so that a @racket[default-expr] is available to evaluate when no
995augmenting method is available. In such a form, @racket[lambda] is a
996literal identifier to separate the @racket[default-expr] from the
997@racket[arg]. When an augmenting method is available, it receives the
998results of the @racket[arg] expressions as arguments.
999
1000Methods that are present in the superclass but not declared with
1001@racket[inherit], @racket[inherit/super], or @racket[inherit/inner] or
1002@racket[rename-super] are not directly accessible in the class
1003(though they can be called with @racket[send]).  Every public method
1004in a superclass is present in a derived class, even if it is not
1005declared with @racket[inherit] in the derived class; the
1006@racket[inherit] clause does not control inheritance, but merely
1007controls lexical scope within a class expression.
1008
1009If a method declared with @racket[inherit], @racket[inherit/super],
1010@racket[inherit/inner], @racket[rename-super], or
1011@racket[rename-inner] is not present in the superclass, the
1012@exnraise[exn:fail:object] when the class expression is evaluated.
1013
1014@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1015
1016@subsubsection[#:tag "extnames"]{Internal and External Names}
1017
1018Each method declared with @racket[public], @racket[override],
1019@racket[augment], @racket[pubment], @racket[overment],
1020@racket[augride], @racket[public-final], @racket[override-final],
1021@racket[augment-final], @racket[inherit], @racket[inherit/super],
1022@racket[inherit/inner], @racket[rename-super], and
1023@racket[rename-inner] can have separate internal and external names
1024when @racket[(internal-id external-id)] is used for declaring the
1025method. The internal name is used to access the method directly within
1026the class expression (including within @racket[super] or
1027@racket[inner] forms), while the external name is used with
1028@racket[send] and @racket[generic] (see @secref["ivaraccess"]).  If
1029a single @racket[id] is provided for a method declaration, the
1030identifier is used for both the internal and external names.
1031
1032Method inheritance, overriding, and augmentation are based on external
1033names only.  Separate internal and external names are required for
1034@racket[rename-super] and @racket[rename-inner] (for historical
1035reasons, mainly).
1036
1037Each @racket[init], @racket[init-field], @racket[field], or
1038@racket[inherit-field] variable similarly has an internal and an
1039external name. The internal name is used within the class to access
1040the variable, while the external name is used outside the class when
1041providing initialization arguments (e.g., to @racket[instantiate]),
1042inheriting a field, or accessing a field externally (e.g., with
1043@racket[class-field-accessor]). As for methods, when inheriting a
1044field with @racket[inherit-field], the external name is matched to an
1045external field name in the superclass, while the internal name is
1046bound in the @racket[class] expression.
1047
1048A single identifier can be used as an internal identifier and an
1049external identifier, and it is possible to use the same identifier as
1050internal and external identifiers for different bindings. Furthermore,
1051within a single class, a single name can be used as an external method
1052name, an external field name, and an external initialization argument
1053name. Overall, each internal identifier must be distinct from all
1054other internal identifiers, each external method name must be distinct
1055from all other method names, each external field name must be distinct
1056from all other field names, and each initialization argument name must
1057be distinct from all other initialization argument names.
1058
1059By default, external names have no lexical scope, which means, for
1060example, that an external method name matches the same syntactic
1061symbol in all uses of @racket[send]. The
1062@racket[define-local-member-name] and @racket[define-member-name] forms
1063introduce scoped external names.
1064
1065When a @racket[class] expression is compiled, identifiers used in
1066place of external names must be symbolically distinct (when the
1067corresponding external names are required to be distinct), otherwise a
1068syntax error is reported. When no external name is bound by
1069@racket[define-member-name], then the actual external names are
1070guaranteed to be distinct when @racket[class] expression is evaluated.
1071When any external name is bound by @racket[define-member-name], the
1072@exnraise[exn:fail:object] by @racket[class] if the actual external
1073names are not distinct.
1074
1075
1076@defform[(define-local-member-name id ...)]{
1077
1078Unless it appears as the top-level definition, binds each @racket[id]
1079so that, within the scope of the definition, each use of each
1080@racket[id] as an external name is resolved to a hidden name generated
1081by the @racket[define-local-member-name] declaration. Thus, methods,
1082fields, and initialization arguments declared with such external-name
1083@racket[id]s are accessible only in the scope of the
1084@racket[define-local-member-name] declaration.  As a top-level
1085definition, @racket[define-local-member-name] binds @racket[id] to its
1086symbolic form.
1087
1088The binding introduced by @racket[define-local-member-name] is a
1089syntax binding that can be exported and imported with
1090@racket[module]s. Each evaluation of a
1091@racket[define-local-member-name] declaration generates a distinct
1092hidden name (except as a top-level definition). The
1093@racket[interface->method-names] procedure does not expose hidden
1094names.
1095
1096@examples[
1097#:eval class-eval
1098(eval:no-prompt
1099 (define-values (r o)
1100   (let ()
1101     (define-local-member-name m)
1102     (define c% (class object%
1103                  (define/public (m) 10)
1104                  (super-new)))
1105     (define o (new c%))
1106
1107     (values (send o m)
1108             o))))
1109
1110r
1111(eval:error (send o m))
1112]}
1113
1114
1115@defform[(define-member-name id key-expr)]{
1116
1117Maps a single external name to an external name that is determined by
1118an expression. The value of @racket[key-expr] must be the result of either a
1119@racket[member-name-key] expression or a @racket[generate-member-key] call.}
1120
1121
1122@defform[(member-name-key identifier)]{
1123
1124Produces a representation of the external name for @racket[id] in the
1125environment of the @racket[member-name-key] expression.}
1126
1127@defproc[(generate-member-key) member-name-key?]{
1128
1129Produces a hidden name, just like the binding for
1130@racket[define-local-member-name].}
1131
1132@defproc[(member-name-key? [v any/c]) boolean?]{
1133
1134Returns @racket[#t] for values produced by @racket[member-name-key]
1135and @racket[generate-member-key], @racket[#f]
1136otherwise.}
1137
1138@defproc[(member-name-key=? [a-key member-name-key?] [b-key member-name-key?]) boolean?]{
1139
1140Produces @racket[#t] if member-name keys @racket[a-key] and
1141@racket[b-key] represent the same external name, @racket[#f]
1142otherwise.}
1143
1144
1145@defproc[(member-name-key-hash-code [a-key member-name-key?]) integer?]{
1146
1147Produces an integer hash code consistent with
1148@racket[member-name-key=?]  comparisons, analogous to
1149@racket[equal-hash-code].}
1150
1151@examples[
1152#:eval class-eval
1153(eval:no-prompt
1154 (define (make-c% key)
1155   (define-member-name m key)
1156   (class object%
1157     (define/public (m) 10)
1158     (super-new))))
1159
1160(send (new (make-c% (member-name-key m))) m)
1161(eval:error (send (new (make-c% (member-name-key p))) m))
1162(send (new (make-c% (member-name-key p))) p)
1163
1164(eval:no-prompt
1165 (define (fresh-c%)
1166   (let ([key (generate-member-key)])
1167     (values (make-c% key) key)))
1168
1169 (define-values (fc% key) (fresh-c%)))
1170
1171(eval:error (send (new fc%) m))
1172(let ()
1173  (define-member-name p key)
1174  (send (new fc%) p))
1175]
1176
1177
1178@; ------------------------------------------------------------------------
1179
1180@section[#:tag "objcreation"]{Creating Objects}
1181
1182The @racket[make-object] procedure creates a new object with
1183by-position initialization arguments, the @racket[new] form
1184creates a new object with by-name initialization arguments, and
1185the @racket[instantiate] form creates a new object with both
1186by-position and by-name initialization arguments.
1187
1188
1189All fields in the newly created object are initially bound to the
1190special @|undefined-const| value (see
1191@secref["void"]). Initialization variables with default value
1192expressions (and no provided value) are also initialized to
1193@|undefined-const|. After argument values are assigned to
1194initialization variables, expressions in @racket[field] clauses,
1195@racket[init-field] clauses with no provided argument,
1196@racket[init] clauses with no provided argument, private field
1197definitions, and other expressions are evaluated. Those
1198expressions are evaluated as they appear in the class expression,
1199from left to right.
1200
1201Sometime during the evaluation of the expressions,
1202superclass-declared initializations must be evaluated once by
1203using the @racket[super-make-object] procedure,
1204@racket[super-new] form, or @racket[super-instantiate] form.
1205
1206By-name initialization arguments to a class that have no matching
1207initialization variable are implicitly added as by-name arguments
1208to a @racket[super-make-object], @racket[super-new], or
1209@racket[super-instantiate] invocation, after the explicit
1210arguments.  If multiple initialization arguments are provided for
1211the same name, the first (if any) is used, and the unused
1212arguments are propagated to the superclass. (Note that converted
1213by-position arguments are always placed before explicit by-name
1214arguments.)  The initialization procedure for the
1215@racket[object%] class accepts zero initialization arguments; if
1216it receives any by-name initialization arguments, then
1217@exnraise[exn:fail:object].
1218
1219If the end of initialization is reached for any class in the
1220hierarchy without invoking the superclass's initialization, the
1221@exnraise[exn:fail:object]. Also, if superclass initialization is
1222invoked more than once, the @exnraise[exn:fail:object].
1223
1224Fields inherited from a superclass are not initialized until the
1225superclass's initialization procedure is invoked. In contrast,
1226all methods are available for an object as soon as the object is
1227created; the overriding of methods is not affected by
1228initialization (unlike objects in C++).
1229
1230
1231
1232@defproc[(make-object [class class?] [init-v any/c] ...) object?]{
1233
1234Creates an instance of @racket[class]. The @racket[init-v]s are
1235passed as initialization arguments, bound to the initialization
1236variables of @racket[class] for the newly created object as
1237described in @secref["clinitvars"]. If @racket[class] is not a
1238class, the @exnraise[exn:fail:contract].}
1239
1240@defform[(new class-expr (id by-name-expr) ...)]{
1241
1242Creates an instance of the value of @racket[class-expr] (which
1243must be a class), and the value of each @racket[by-name-expr] is
1244provided as a by-name argument for the corresponding
1245@racket[id].}
1246
1247@defform[(instantiate class-expr (by-pos-expr ...) (id by-name-expr) ...)]{
1248
1249Creates an instance of the value of @racket[class-expr] (which
1250must be a class), and the values of the @racket[by-pos-expr]s are
1251provided as by-position initialization arguments. In addition,
1252the value of each @racket[by-name-expr] is provided as a by-name
1253argument for the corresponding @racket[id].}
1254
1255@defidform[super-make-object]{
1256
1257Produces a procedure that takes by-position arguments an invokes
1258superclass initialization. See @secref["objcreation"] for more
1259information.}
1260
1261
1262@defform[(super-instantiate (by-pos-expr ...) (id by-expr ...) ...)]{
1263
1264
1265Invokes superclass initialization with the specified by-position and
1266by-name arguments. See @secref["objcreation"] for more
1267information.}
1268
1269
1270@defform[(super-new (id by-name-expr ...) ...)]{
1271
1272Invokes superclass initialization with the specified by-name
1273arguments. See @secref["objcreation"] for more information.}
1274
1275@; ------------------------------------------------------------------------
1276
1277@section[#:tag "ivaraccess"]{Field and Method Access}
1278
1279In expressions within a class definition, the initialization
1280variables, fields, and methods of the class are all part of the
1281environment. Within a method body, only the fields and other methods
1282of the class can be referenced; a reference to any other
1283class-introduced identifier is a syntax error.  Elsewhere within the
1284class, all class-introduced identifiers are available, and fields and
1285initialization variables can be mutated with @racket[set!].
1286
1287@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1288
1289@subsection[#:tag "methodcalls"]{Methods}
1290
1291Method names used within a class can only be used in the procedure position
1292of an application expression; any other use is a syntax error.
1293
1294To allow methods to be applied to lists of arguments, a method
1295application can have the following form:
1296
1297@specsubform[
1298(method-id arg ... . arg-list-expr)
1299]
1300
1301This form calls the method in a way analogous to @racket[(apply
1302_method-id _arg ... _arg-list-expr)]. The @racket[arg-list-expr]
1303must not be a parenthesized expression.
1304
1305Methods are called from outside a class with the @racket[send],
1306@racket[send/apply], and @racket[send/keyword-apply] forms.
1307
1308@defform*[[(send obj-expr method-id arg ...)
1309           (send obj-expr method-id arg ... . arg-list-expr)]]{
1310
1311Evaluates @racket[obj-expr] to obtain an object, and calls the method
1312with (external) name @racket[method-id] on the object, providing the
1313@racket[arg] results as arguments. Each @racket[arg] is as for
1314@racket[#%app]: either @racket[_arg-expr] or @racket[_keyword
1315_arg-expr]. In the second form, @racket[arg-list-expr] cannot be a
1316parenthesized expression.
1317
1318If @racket[obj-expr] does not produce an object, the
1319@exnraise[exn:fail:contract]. If the object has no public method named
1320@racket[method-id], the @exnraise[exn:fail:object].}
1321
1322@defform[(send/apply obj-expr method-id arg ... arg-list-expr)]{
1323
1324Like the dotted form of @racket[send], but @racket[arg-list-expr] can
1325be any expression.}
1326
1327@defform[(send/keyword-apply obj-expr method-id
1328                             keyword-list-expr value-list-expr
1329                             arg ... arg-list-expr)]{
1330
1331Like @racket[send/apply], but with expressions for keyword and
1332argument lists like @racket[keyword-apply].}
1333
1334@defproc[(dynamic-send [obj object?]
1335                       [method-name symbol?]
1336                       [v any/c] ...
1337                       [#:<kw> kw-arg any/c] ...) any]{
1338
1339Calls the method on @racket[obj] whose name matches
1340@racket[method-name], passing along all given @racket[v]s and
1341@racket[kw-arg]s.}
1342
1343
1344@defform/subs[(send* obj-expr msg ...+)
1345              ([msg (method-id arg ...)
1346                    (method-id arg ... . arg-list-expr)])]{
1347
1348Calls multiple methods (in order) of the same object. Each
1349@racket[msg] corresponds to a use of @racket[send].
1350
1351For example,
1352
1353@racketblock[
1354(send* edit (begin-edit-sequence)
1355            (insert "Hello")
1356            (insert #\newline)
1357            (end-edit-sequence))
1358]
1359
1360is the same as
1361
1362@racketblock[
1363(let ([o edit])
1364  (send o begin-edit-sequence)
1365  (send o insert "Hello")
1366  (send o insert #\newline)
1367  (send o end-edit-sequence))
1368]}
1369
1370@defform/subs[(send+ obj-expr msg ...)
1371              ([msg (method-id arg ...)
1372                    (method-id arg ... . arg-list-expr)])]{
1373
1374Calls methods (in order) starting with the object produced by
1375@racket[obj-expr]. Each method call will be invoked on the result of
1376the last method call, which is expected to be an object. Each
1377@racket[msg] corresponds to a use of @racket[send].
1378
1379This is the functional analogue of @racket[send*].
1380
1381@examples[#:eval class-eval
1382(eval:no-prompt
1383 (define point%
1384   (class object%
1385     (super-new)
1386     (init-field [x 0] [y 0])
1387     (define/public (move-x dx)
1388       (new this% [x (+ x dx)]))
1389     (define/public (move-y dy)
1390       (new this% [y (+ y dy)])))))
1391
1392(send+ (new point%)
1393       (move-x 5)
1394       (move-y 7)
1395       (move-x 12))
1396]}
1397
1398@defform[(with-method ((id (obj-expr method-id)) ...)
1399           body ...+)]{
1400
1401Extracts methods from an object and binds a local name that can be
1402applied directly (in the same way as declared methods within a class)
1403for each method. Each @racket[obj-expr] must produce an object,
1404which must have a public method named by the corresponding
1405@racket[method-id]. The corresponding @racket[id] is bound so that it
1406can be applied directly (see @secref["methodcalls"]).
1407
1408Example:
1409
1410@racketblock[
1411(let ([s (new stack%)])
1412  (with-method ([push (s push!)]
1413                [pop (s pop!)])
1414    (push 10)
1415    (push 9)
1416    (pop)))
1417]
1418
1419is the same as
1420
1421@racketblock[
1422(let ([s (new stack%)])
1423  (send s push! 10)
1424  (send s push! 9)
1425  (send s pop!))
1426]}
1427
1428@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1429
1430@subsection{Fields}
1431
1432@defform[(get-field id obj-expr)]{
1433
1434Extracts the field with (external) name @racket[id] from the value of
1435@racket[obj-expr].
1436
1437If @racket[obj-expr] does not produce an object, the
1438@exnraise[exn:fail:contract]. If the object has no @racket[id] field,
1439the @exnraise[exn:fail:object].}
1440
1441@defproc[(dynamic-get-field [field-name symbol?] [obj object?]) any/c]{
1442
1443Extracts the field from @racket[obj] with the (external) name that
1444matches @racket[field-name]. If the object has no field matching @racket[field-name],
1445the @exnraise[exn:fail:object].}
1446
1447@defform[(set-field! id obj-expr expr)]{
1448
1449Sets the field with (external) name @racket[id] from the value of
1450@racket[obj-expr] to the value of @racket[expr].
1451
1452If @racket[obj-expr] does not produce an object, the
1453@exnraise[exn:fail:contract].  If the object has no @racket[id] field,
1454the @exnraise[exn:fail:object].}
1455
1456@defproc[(dynamic-set-field! [field-name symbol?] [obj object?] [v any/c]) void?]{
1457
1458Sets the field from @racket[obj] with the (external) name that
1459matches @racket[field-name] to @racket[v]. If the object has no field matching @racket[field-name],
1460the @exnraise[exn:fail:object].}
1461
1462@defform[(field-bound? id obj-expr)]{
1463
1464Produces @racket[#t] if the object result of @racket[obj-expr] has a
1465field with (external) name @racket[id], @racket[#f] otherwise.
1466
1467If @racket[obj-expr] does not produce an object, the
1468@exnraise[exn:fail:contract].}
1469
1470@defform[(class-field-accessor class-expr field-id)]{
1471
1472Returns an accessor procedure that takes an instance of the class
1473produced by @racket[class-expr] and returns the value of the object's
1474field with (external) name @racket[field-id].
1475
1476If @racket[class-expr] does not produce a class, the
1477@exnraise[exn:fail:contract]. If the class has no @racket[field-id]
1478field, the @exnraise[exn:fail:object].}
1479
1480@defform[(class-field-mutator class-expr field-id)]{
1481
1482Returns a mutator procedure that takes an instance of the class
1483produced by @racket[class-expr] and a value, and sets the value of the
1484object's field with (external) name @racket[field-id] to the given
1485value. The result is @|void-const|.
1486
1487If @racket[class-expr] does not produce a class, the
1488@exnraise[exn:fail:contract]. If the class has no @racket[field-id]
1489field, the @exnraise[exn:fail:object].}
1490
1491@; - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1492
1493@subsection{Generics}
1494
1495A @deftech{generic} can be used instead of a method name to avoid the
1496cost of relocating a method by name within a class.
1497
1498@defform[(generic class-or-interface-expr id)]{
1499
1500Produces a generic that works on instances of the class or interface
1501produced by @racket[class-or-interface-expr] (or an instance of a
1502class/interface derived from @racket[class-or-interface]) to call the
1503method with (external) name @racket[id].
1504
1505If @racket[class-or-interface-expr] does not produce a class or
1506interface, the @exnraise[exn:fail:contract]. If the resulting class or
1507interface does not contain a method named @racket[id], the
1508@exnraise[exn:fail:object].}
1509
1510@defform*[[(send-generic obj-expr generic-expr arg ...)
1511           (send-generic obj-expr generic-expr arg ... . arg-list-expr)]]{
1512
1513Calls a method of the object produced by @racket[obj-expr] as
1514indicated by the generic produced by @racket[generic-expr]. Each
1515@racket[arg] is as for @racket[#%app]: either @racket[_arg-expr] or
1516@racket[_keyword _arg-expr]. The second form is analogous to calling a
1517procedure with @racket[apply], where @racket[arg-list-expr] is not a
1518parenthesized expression.
1519
1520If @racket[obj-expr] does not produce an object, or if
1521@racket[generic-expr] does not produce a generic, the
1522@exnraise[exn:fail:contract]. If the result of @racket[obj-expr] is
1523not an instance of the class or interface encapsulated by the result
1524of @racket[generic-expr], the @exnraise[exn:fail:object].}
1525
1526@defproc[(make-generic [type (or/c class? interface?)]
1527                       [method-name symbol?])
1528         generic?]{
1529
1530Like the @racket[generic] form, but as a procedure that accepts a
1531symbolic method name.}
1532
1533@; ------------------------------------------------------------------------
1534
1535@section[#:tag "mixins"]{Mixins}
1536
1537@defform[(mixin (interface-expr ...) (interface-expr ...)
1538           class-clause ...)]{
1539
1540Produces a @deftech{mixin}, which is a procedure that encapsulates a
1541class extension, leaving the superclass unspecified.  Each time that a
1542mixin is applied to a specific superclass, it produces a new derived
1543class using the encapsulated extension.
1544
1545The given class must implement interfaces produced by the first set of
1546@racket[interface-expr]s.  The result of the procedure is a subclass
1547of the given class that implements the interfaces produced by the
1548second set of @racket[interface-expr]s. The @racket[class-clause]s are
1549as for @racket[class*], to define the class extension encapsulated by
1550the mixin.
1551
1552Evaluation of a @racket[mixin] form checks that the
1553@racket[class-clause]s are consistent with both sets of
1554@racket[interface-expr]s.}
1555
1556@; ------------------------------------------------------------------------
1557
1558@section[#:tag "trait"]{Traits}
1559
1560@note-lib-only[racket/trait]
1561
1562A @deftech{trait} is a collection of methods that can be converted to
1563a @tech{mixin} and then applied to a @tech{class}. Before a trait is
1564converted to a mixin, the methods of a trait can be individually
1565renamed, and multiple traits can be merged to form a new trait.
1566
1567@defform/subs[#:literals (public pubment public-final override override-final overment augment augride
1568                          augment-final private inherit inherit/super inherit/inner rename-super
1569                          field inherit-field)
1570
1571              (trait trait-clause ...)
1572              ([trait-clause (public maybe-renamed ...)
1573                             (pubment maybe-renamed ...)
1574                             (public-final maybe-renamed ...)
1575                             (override maybe-renamed ...)
1576                             (overment maybe-renamed ...)
1577                             (override-final maybe-renamed ...)
1578                             (augment maybe-renamed ...)
1579                             (augride maybe-renamed ...)
1580                             (augment-final maybe-renamed ...)
1581                             (inherit maybe-renamed ...)
1582                             (inherit/super maybe-renamed ...)
1583                             (inherit/inner maybe-renamed ...)
1584                             method-definition
1585                             (field field-declaration ...)
1586                             (inherit-field maybe-renamed ...)])]{
1587
1588Creates a @tech{trait}.  The body of a @racket[trait] form is similar to the
1589body of a @racket[class*] form, but restricted to non-private method
1590definitions.  In particular, the grammar of
1591@racket[maybe-renamed], @racket[method-definition], and
1592@racket[field-declaration] are the same as for @racket[class*], and
1593every @racket[method-definition] must have a corresponding declaration
1594(one of @racket[public], @racket[override], etc.).  As in
1595@racket[class], uses of method names in direct calls, @racket[super]
1596calls, and @racket[inner] calls depend on bringing method names into
1597scope via @racket[inherit], @racket[inherit/super],
1598@racket[inherit/inner], and other method declarations in the same
1599trait; an exception, compared to @racket[class] is that
1600@racket[overment] binds a method name only in the corresponding
1601method, and not in other methods of the same trait. Finally, macros
1602such as @racket[public*] and @racket[define/public] work in
1603@racket[trait] as in @racket[class].
1604
1605External identifiers in @racket[trait], @racket[trait-exclude],
1606@racket[trait-exclude-field], @racket[trait-alias],
1607@racket[trait-rename], and @racket[trait-rename-field] forms are
1608subject to binding via @racket[define-member-name] and
1609@racket[define-local-member-name]. Although @racket[private] methods
1610or fields are not allowed in a @racket[trait] form, they can be
1611simulated by using a @racket[public] or @racket[field] declaration and
1612a name whose scope is limited to the @racket[trait] form.}
1613
1614
1615@defproc[(trait? [v any/c]) boolean?]{
1616
1617Returns @racket[#t] if @racket[v] is a trait, @racket[#f] otherwise.}
1618
1619
1620@defproc[(trait->mixin [tr trait?]) (class? . -> . class?)]{
1621
1622Converts a @tech{trait} to a @tech{mixin}, which can be applied to a
1623@tech{class} to produce a new @tech{class}. An expression of the form
1624
1625@racketblock[
1626(trait->mixin
1627 (trait
1628   _trait-clause ...))
1629]
1630
1631is equivalent to
1632
1633@racketblock[
1634(lambda (%)
1635  (class %
1636    _trait-clause ...
1637    (super-new)))
1638]
1639
1640Normally, however, a trait's methods are changed and combined with
1641other traits before converting to a mixin.}
1642
1643
1644@defproc[(trait-sum [tr trait?] ...+) trait?]{
1645
1646Produces a @tech{trait} that combines all of the methods of the given
1647@racket[tr]s. For example,
1648
1649@racketblock[
1650(define t1
1651  (trait
1652    (define/public (m1) 1)))
1653(define t2
1654  (trait
1655    (define/public (m2) 2)))
1656(define t3 (trait-sum t1 t2))
1657]
1658
1659creates a trait @racket[t3] that is equivalent to
1660
1661@racketblock[
1662(trait
1663  (define/public (m1) 1)
1664  (define/public (m2) 2))
1665]
1666
1667but @racket[t1] and @racket[t2] can still be used individually or
1668combined with other traits.
1669
1670When traits are combined with @racket[trait-sum], the combination
1671drops @racket[inherit], @racket[inherit/super],
1672@racket[inherit/inner], and @racket[inherit-field] declarations when a
1673definition is supplied for the same method or field name by another
1674trait. The @racket[trait-sum] operation fails (the
1675@exnraise[exn:fail:contract]) if any of the traits to combine define a
1676method or field with the same name, or if an @racket[inherit/super] or
1677@racket[inherit/inner] declaration to be dropped is inconsistent with
1678the supplied definition. In other words, declaring a method with
1679@racket[inherit], @racket[inherit/super], or @racket[inherit/inner],
1680does not count as defining the method; at the same time, for example,
1681a trait that contains an @racket[inherit/super] declaration for a
1682method @racket[m] cannot be combined with a trait that defines
1683@racket[m] as @racket[augment], since no class could satisfy the
1684requirements of both @racket[augment] and @racket[inherit/super] when
1685the trait is later converted to a mixin and applied to a class.}
1686
1687
1688@defform[(trait-exclude trait-expr id)]{
1689
1690Produces a new @tech{trait} that is like the @tech{trait} result of
1691@racket[trait-expr], but with the definition of a method named by
1692@racket[id] removed; as the method definition is removed, either an
1693@racket[inherit], @racket[inherit/super], or @racket[inherit/inner]
1694declaration is added:
1695
1696@itemize[
1697
1698 @item{A method declared with @racket[public], @racket[pubment], or
1699  @racket[public-final] is replaced with an @racket[inherit]
1700  declaration.}
1701
1702 @item{A method declared with @racket[override] or @racket[override-final]
1703 is replaced with an @racket[inherit/super] declaration.}
1704
1705  @item{A method declared with @racket[augment], @racket[augride], or
1706  @racket[augment-final] is replaced with an @racket[inherit/inner] declaration.}
1707
1708 @item{A method declared with @racket[overment] is not replaced
1709  with any @racket[inherit] declaration.}
1710
1711]
1712
1713If the trait produced by @racket[trait-expr] has no method definition for
1714@racket[id], the @exnraise[exn:fail:contract].}
1715
1716
1717@defform[(trait-exclude-field trait-expr id)]{
1718
1719Produces a new @tech{trait} that is like the @tech{trait} result of
1720@racket[trait-expr], but with the definition of a field named by
1721@racket[id] removed; as the field definition is removed, an
1722@racket[inherit-field] declaration is added.}
1723
1724
1725@defform[(trait-alias trait-expr id new-id)]{
1726
1727Produces a new @tech{trait} that is like the @tech{trait} result of
1728@racket[trait-expr], but the definition and declaration of the method
1729named by @racket[id] is duplicated with the name @racket[new-id]. The
1730consistency requirements for the resulting trait are the same as for
1731@racket[trait-sum], otherwise the @exnraise[exn:fail:contract]. This
1732operation does not rename any other use of @racket[id], such as in
1733method calls (even method calls to @racket[identifier] in the cloned
1734definition for @racket[new-id]).}
1735
1736
1737@defform[(trait-rename trait-expr id new-id)]{
1738
1739Produces a new @tech{trait} that is like the @tech{trait} result of
1740@racket[trait-expr], but all definitions and references to methods
1741named @racket[id] are replaced by definitions and references to
1742methods named by @racket[new-id]. The consistency requirements for the
1743resulting trait are the same as for @racket[trait-sum], otherwise the
1744@exnraise[exn:fail:contract].}
1745
1746
1747@defform[(trait-rename-field trait-expr id new-id)]{
1748
1749Produces a new @tech{trait} that is like the @tech{trait} result of
1750@racket[trait-expr], but all definitions and references to fields
1751named @racket[id] are replaced by definitions and references to fields
1752named by @racket[new-id]. The consistency requirements for the
1753resulting trait are the same as for @racket[trait-sum], otherwise the
1754@exnraise[exn:fail:contract].}
1755
1756@; ------------------------------------------------------------------------
1757
1758@section{Object and Class Contracts}
1759
1760@defform/subs[
1761#:literals (field init init-field inherit inherit-field super inner override augment augride absent)
1762
1763(class/c maybe-opaque member-spec ...)
1764
1765([maybe-opaque
1766  (code:line)
1767  (code:line #:opaque)
1768  (code:line #:opaque #:ignore-local-member-names)]
1769
1770 [member-spec
1771  method-spec
1772  (field field-spec ...)
1773  (init field-spec ...)
1774  (init-field field-spec ...)
1775  (inherit method-spec ...)
1776  (inherit-field field-spec ...)
1777  (super method-spec ...)
1778  (inner method-spec ...)
1779  (override method-spec ...)
1780  (augment method-spec ...)
1781  (augride method-spec ...)
1782  (absent absent-spec ...)]
1783
1784 [method-spec
1785  method-id
1786  (method-id method-contract-expr)]
1787 [field-spec
1788  field-id
1789  (field-id contract-expr)]
1790 [absent-spec
1791  method-id
1792  (field field-id ...)])]{
1793Produces a contract for a class.
1794
1795There are two major categories of contracts listed in a @racket[class/c]
1796form: external and internal contracts. External contracts govern behavior
1797when an object is instantiated from a class or when methods or fields are
1798accessed via an object of that class. Internal contracts govern behavior
1799when method or fields are accessed within the class hierarchy.  This
1800separation allows for stronger contracts for class clients and weaker
1801contracts for subclasses.
1802
1803Method contracts must contain an additional initial argument which corresponds
1804to the implicit @racket[this] parameter of the method.  This allows for
1805contracts which discuss the state of the object when the method is called
1806(or, for dependent contracts, in other parts of the contract).  Alternative
1807contract forms, such as @racket[->m], are provided as a shorthand
1808for writing method contracts.
1809
1810Methods and fields listed in an @racket[absent] clause must @emph{not} be present in the class.
1811
1812A class contract can be specified to be @emph{opaque} with the @racket[#:opaque]
1813keyword. An opaque class contract will only accept a class that defines
1814exactly the external methods and fields specified by the contract. A contract error
1815is raised if the contracted class contains any methods or fields that are
1816not specified. Methods or fields with local member names (i.e., defined with
1817@racket[define-local-member-name]) are ignored for this check if
1818@racket[#:ignore-local-member-names] is provided.
1819
1820The external contracts are as follows:
1821
1822@itemize[
1823 @item{An external method contract without a tag describes the behavior
1824   of the implementation of @racket[method-id] on method sends to an
1825   object of the contracted class.  This contract will continue to be
1826   checked in subclasses until the contracted class's implementation is
1827   no longer the entry point for dynamic dispatch.
1828
1829   If only the field name is present, this is equivalent to insisting only
1830   that the method is present in the class.
1831
1832   @examples[#:eval class-eval
1833                (eval:no-prompt
1834                 (define woody%
1835                   (class object%
1836                     (define/public (draw who)
1837                       (format "reach for the sky, ~a" who))
1838                     (super-new)))
1839
1840                 (define/contract woody+c%
1841                   (class/c [draw (->m symbol? string?)])
1842                   woody%))
1843
1844                (send (new woody%) draw #f)
1845                (send (new woody+c%) draw 'zurg)
1846                (eval:error (send (new woody+c%) draw #f))]
1847   }
1848 @item{An external field contract, tagged with @racket[field], describes the
1849   behavior of the value contained in that field when accessed from outside
1850   the class.  Since fields may be mutated, these contracts
1851   are checked on any external access (via @racket[get-field])
1852   and external mutations (via @racket[set-field!]) of the field.
1853
1854   If only the field name is present, this is equivalent to using the
1855   contract @racket[any/c] (but it is checked more efficiently).
1856
1857   @examples[#:eval class-eval
1858                (eval:no-prompt
1859                 (define woody/hat%
1860                   (class woody%
1861                     (field [hat-location 'uninitialized])
1862                     (define/public (lose-hat) (set! hat-location 'lost))
1863                     (define/public (find-hat) (set! hat-location 'on-head))
1864                     (super-new)))
1865                 (define/contract woody/hat+c%
1866                   (class/c [draw (->m symbol? string?)]
1867                            [lose-hat (->m void?)]
1868                            [find-hat (->m void?)]
1869                            (field [hat-location (or/c 'on-head 'lost)]))
1870                   woody/hat%))
1871
1872                (get-field hat-location (new woody/hat%))
1873                (let ([woody (new woody/hat+c%)])
1874                  (send woody lose-hat)
1875                  (get-field hat-location woody))
1876                (eval:error (get-field hat-location (new woody/hat+c%)))
1877                (eval:error
1878                 (let ([woody (new woody/hat+c%)])
1879                   (set-field! hat-location woody 'under-the-dresser)))]
1880
1881   }
1882 @item{An initialization argument contract, tagged with @racket[init],
1883   describes the expected behavior of the value paired with that name
1884   during class instantiation.  The same name can be provided more than
1885   once, in which case the first such contract in the @racket[class/c]
1886   form is applied to the first value tagged with that name in the list
1887   of initialization arguments, and so on.
1888
1889   If only the initialization argument name is present, this is equivalent to using the
1890   contract @racket[any/c] (but it is checked more efficiently).
1891
1892   @examples[#:eval class-eval
1893                (eval:no-prompt
1894                 (define woody/init-hat%
1895                   (class woody%
1896                     (init init-hat-location)
1897                     (field [hat-location init-hat-location])
1898                     (define/public (lose-hat) (set! hat-location 'lost))
1899                     (define/public (find-hat) (set! hat-location 'on-head))
1900                     (super-new)))
1901                 (define/contract woody/init-hat+c%
1902                   (class/c [draw (->m symbol? string?)]
1903                            [lose-hat (->m void?)]
1904                            [find-hat (->m void?)]
1905                            (init [init-hat-location (or/c 'on-head 'lost)])
1906                            (field [hat-location (or/c 'on-head 'lost)]))
1907                   woody/init-hat%))
1908                (get-field hat-location
1909                           (new woody/init-hat+c%
1910                                [init-hat-location 'lost]))
1911                (eval:error
1912                 (get-field hat-location
1913                            (new woody/init-hat+c%
1914                                 [init-hat-location 'slinkys-mouth])))]
1915
1916   }
1917 @item{The contracts listed in an @racket[init-field] section are
1918   treated as if each contract appeared in an @racket[init] section and
1919   a @racket[field] section.}
1920]
1921
1922The internal contracts restrict the behavior of method calls
1923made between classes and their subclasses; such calls are not
1924controlled by the class contracts described above.
1925
1926As with the external contracts, when a method or field name is specified
1927 but no contract appears, the contract is satisfied merely with the
1928 presence of the corresponding field or method.
1929
1930@itemize[
1931 @item{A method contract tagged with @racket[inherit] describes the
1932   behavior of the method when invoked directly (i.e., via
1933   @racket[inherit]) in any subclass of the contracted class.  This
1934   contract, like external method contracts, applies until the
1935   contracted class's method implementation is no longer the entry point
1936   for dynamic dispatch.
1937
1938   @examples[#:eval class-eval
1939                (new (class woody+c%
1940                       (inherit draw)
1941                       (super-new)
1942                       (printf "woody sez: “~a”\n" (draw "evil dr porkchop"))))
1943                (eval:no-prompt
1944                 (define/contract woody+c-inherit%
1945                   (class/c (inherit [draw (->m symbol? string?)]))
1946                   woody+c%))
1947                (eval:error
1948                 (new (class woody+c-inherit%
1949                        (inherit draw)
1950                        (printf "woody sez: ~a\n" (draw "evil dr porkchop")))))]
1951
1952   }
1953  @item{A method contract tagged with @racket[super] describes the behavior of
1954   @racket[method-id] when called by the @racket[super] form in a
1955   subclass.  This contract only affects @racket[super] calls in
1956   subclasses which call the contract class's implementation of
1957   @racket[method-id].
1958
1959   This example shows how to extend the @racket[draw] method
1960   so that if it is passed two arguments, it combines two
1961   calls to the original @racket[draw] method, but with a
1962   contract the controls how the @racket[super] methods must
1963   be invoked.
1964
1965   @examples[#:eval class-eval
1966                (eval:no-prompt
1967
1968  (define/contract woody%+s
1969    (class/c (super [draw (->m symbol? string?)]))
1970    (class object%
1971      (define/public (draw who)
1972        (format "reach for the sky, ~a" who))
1973      (super-new)))
1974
1975  (define woody2+c%
1976    (class woody%+s
1977      (define/override draw
1978        (case-lambda
1979          [(a) (super draw a)]
1980          [(a b) (string-append (super draw a)
1981                                " and "
1982                                (super draw b))]))
1983      (super-new))))
1984
1985                (send (new woody2+c%) draw 'evil-dr-porkchop  'zurg)
1986                (eval:error (send (new woody2+c%) draw "evil dr porkchop" "zurg"))]
1987
1988   The last call signals an error blaming @racket[woody2%+c] because
1989   there is no contract checking the initial @racket[draw] call and
1990   the super-call violates its contract.
1991   }
1992 @item{A method contract tagged with @racket[inner] describes the
1993   behavior the class expects of an augmenting method in a subclass.
1994   This contract affects any implementations of @racket[method-id] in
1995   subclasses which can be called via @racket[inner] from the contracted
1996   class.  This means a subclass which implements @racket[method-id] via
1997   @racket[augment] or @racket[overment] stop future subclasses from
1998   being affected by the contract, since further extension cannot be
1999   reached via the contracted class.}
2000 @item{A method contract tagged with @racket[override] describes the
2001   behavior expected by the contracted class for @racket[method-id] when
2002   called directly (i.e. by the application @racket[(method-id ...)]).
2003   This form can only be used if overriding the method in subclasses
2004   will change the entry point to the dynamic dispatch chain (i.e., the
2005   method has never been augmentable).
2006
2007   This time, instead of overriding @racket[draw] to support
2008   two arguments, we can make a new method, @racket[draw2] that
2009   takes the two arguments and calls @racket[draw]. We also
2010   add a contract to make sure that overriding @racket[draw]
2011   doesn't break @racket[draw2].
2012
2013   @examples[#:eval class-eval
2014                (eval:no-prompt
2015                 (define/contract woody2+override/c%
2016                   (class/c (override [draw (->m symbol? string?)]))
2017                   (class woody+c%
2018                     (inherit draw)
2019                     (define/public (draw2 a b)
2020                       (string-append (draw a)
2021                                      " and "
2022                                      (draw b)))
2023                     (super-new)))
2024
2025                 (define woody2+broken-draw
2026                   (class woody2+override/c%
2027                     (define/override (draw x)
2028                       'not-a-string)
2029                     (super-new))))
2030
2031                (eval:error
2032                 (send (new woody2+broken-draw) draw2
2033                       'evil-dr-porkchop
2034                       'zurg))]
2035
2036
2037   }
2038 @item{A method contract tagged with either @racket[augment] or
2039   @racket[augride] describes the behavior provided by the contracted
2040   class for @racket[method-id] when called directly from subclasses.
2041   These forms can only be used if the method has previously been
2042   augmentable, which means that no augmenting or overriding
2043   implementation will change the entry point to the dynamic dispatch
2044   chain.  @racket[augment] is used when subclasses can augment the
2045   method, and @racket[augride] is used when subclasses can override the
2046   current augmentation.}
2047 @item{A field contract tagged with @racket[inherit-field] describes
2048   the behavior of the value contained in that field when accessed
2049   directly (i.e., via @racket[inherit-field]) in any subclass of the
2050   contracted class.  Since fields may be mutated, these contracts are
2051   checked on any access and/or mutation of the field that occurs in
2052   such subclasses.}
2053
2054@history[#:changed "6.1.1.8"
2055         @string-append{Opaque class/c now optionally ignores local
2056                        member names if an additional keyword is supplied.}]
2057]}
2058
2059@defform[(absent absent-spec ...)]{
2060See @racket[class/c]; use outside of a @racket[class/c] form is a syntax error.
2061}
2062
2063@defform[(->m dom ... range)]{
2064Similar to @racket[->], except that the domain of the resulting contract
2065contains one more element than the stated domain, where the first
2066(implicit) argument is contracted with @racket[any/c].  This contract is
2067useful for writing simpler method contracts when no properties of
2068@racket[this] need to be checked.}
2069
2070@defform[(->*m (mandatory-dom ...) (optional-dom ...) rest range)]{
2071Similar to @racket[->*], except that the mandatory domain of the
2072resulting contract contains one more element than the stated domain,
2073where the first (implicit) argument is contracted with
2074@racket[any/c]. This contract is useful for writing simpler method
2075contracts when no properties of @racket[this] need to be checked.}
2076
2077@defform[(case->m (-> dom ... rest range) ...)]{
2078Similar to @racket[case->], except that the mandatory domain of each
2079case of the resulting contract contains one more element than the stated
2080domain, where the first (implicit) argument is contracted with
2081@racket[any/c]. This contract is useful for writing simpler method
2082contracts when no properties of @racket[this] need to be checked.}
2083
2084@defform[(->dm (mandatory-dependent-dom ...)
2085               (optional-dependent-dom ...)
2086               dependent-rest
2087               pre-cond
2088               dep-range)]{
2089Similar to @racket[->d], except that the mandatory domain of the resulting contract
2090contains one more element than the stated domain, where the first (implicit) argument is contracted
2091with @racket[any/c]. In addition, @racket[this] is appropriately bound in the body of the contract.
2092This contract is useful for writing simpler method contracts when no properties
2093of @racket[this] need to be checked.}
2094
2095@defform/subs[
2096#:literals (field)
2097
2098(object/c member-spec ...)
2099
2100([member-spec
2101  method-spec
2102  (field field-spec ...)]
2103
2104 [method-spec
2105  method-id
2106  (method-id method-contract)]
2107 [field-spec
2108  field-id
2109  (field-id contract-expr)])]{
2110Produces a contract for an object.
2111
2112Unlike the older form @racket[object-contract], but like
2113@racket[class/c], arbitrary contract expressions are allowed.
2114Also, method contracts for @racket[object/c] follow those for
2115@racket[class/c].  An object wrapped with @racket[object/c]
2116behaves as if its class had been wrapped with the equivalent
2117@racket[class/c] contract.
2118}
2119
2120@defproc[(instanceof/c [class-contract contract?]) contract?]{
2121Produces a contract for an object, where the object is an
2122instance of a class that conforms to @racket[class-contract].
2123}
2124
2125@defproc[(dynamic-object/c [method-names (listof symbol?)]
2126                           [method-contracts (listof contract?)]
2127                           [field-names (listof symbol?)]
2128                           [field-contracts (listof contract?)])
2129         contract?]{
2130Produces a contract for an object, similar to @racket[object/c] but
2131where the names and contracts for both methods and fields can be
2132computed dynamically. The list of names and contracts for both
2133methods and field respectively must have the same lengths.
2134}
2135
2136@defform/subs[
2137#:literals (field -> ->* ->d)
2138
2139(object-contract member-spec ...)
2140
2141([member-spec
2142  (method-id method-contract)
2143  (field field-id contract-expr)]
2144
2145 [method-contract
2146  (-> dom ... range)
2147  (->* (mandatory-dom ...)
2148       (optional-dom ...)
2149       rest
2150       range)
2151  (->d (mandatory-dependent-dom ...)
2152       (optional-dependent-dom ...)
2153       dependent-rest
2154       pre-cond
2155       dep-range)]
2156
2157 [dom dom-expr (code:line keyword dom-expr)]
2158 [range range-expr (values range-expr ...) any]
2159 [mandatory-dom dom-expr (code:line keyword dom-expr)]
2160 [optional-dom dom-expr (code:line keyword dom-expr)]
2161 [rest (code:line) (code:line #:rest rest-expr)]
2162 [mandatory-dependent-dom [id dom-expr] (code:line keyword [id dom-expr])]
2163 [optional-dependent-dom [id dom-expr] (code:line keyword [id dom-expr])]
2164 [dependent-rest (code:line) (code:line #:rest id rest-expr)]
2165 [pre-cond (code:line) (code:line #:pre-cond boolean-expr)]
2166 [dep-range any
2167            (code:line [id range-expr] post-cond)
2168            (code:line (values [id range-expr] ...) post-cond)]
2169 [post-cond (code:line) (code:line #:post-cond boolean-expr)]
2170)]{
2171
2172Produces a contract for an object.
2173
2174Each of the contracts for a method has the same semantics as
2175the corresponding function contract, but the syntax of the
2176method contract must be written directly in the body of the
2177object-contract---much like the way that methods in class
2178definitions use the same syntax as regular function
2179definitions, but cannot be arbitrary procedures.  Unlike the
2180method contracts for @racket[class/c], the implicit @racket[this]
2181argument is not part of the contract.  To allow for the use of
2182@racket[this] in dependent contracts, @racket[->d] contracts
2183implicitly bind @racket[this] to the object itself.}
2184
2185
2186@defthing[mixin-contract contract?]{
2187
2188A @tech{function contract} that recognizes mixins. It guarantees that
2189the input to the function is a class and the result of the function is
2190a subclass of the input.}
2191
2192@defproc[(make-mixin-contract [type (or/c class? interface?)] ...) contract?]{
2193
2194Produces a @tech{function contract} that guarantees the input to the
2195function is a class that implements/subclasses each @racket[type], and
2196that the result of the function is a subclass of the input.}
2197
2198@defproc[(is-a?/c [type (or/c class? interface?)]) flat-contract?]{
2199
2200Accepts a class or interface and returns a flat contract that
2201recognizes objects that instantiate the class/interface.
2202
2203See @racket[is-a?].}
2204
2205@defproc[(implementation?/c [interface interface?]) flat-contract?]{
2206
2207Returns a flat contract that recognizes classes that implement
2208@racket[interface].
2209
2210See @racket[implementation?].}
2211
2212@defproc[(subclass?/c [class class?]) flat-contract?]{
2213
2214Returns a flat contract that recognizes classes that
2215are subclasses of @racket[class].
2216
2217See @racket[subclass?].}
2218
2219@; ------------------------------------------------------------------------
2220
2221@section[#:tag "objectequality"]{Object Equality and Hashing}
2222
2223By default, objects that are instances of different classes or that
2224are instances of a non-transparent class are @racket[equal?] only if
2225they are @racket[eq?]. Like transparent structures, two objects that
2226are instances of the same transparent class (i.e., every superclass of
2227the class has @racket[#f] as its inspector) are @racket[equal?] when
2228their field values are @racket[equal?].
2229
2230To customize the way that a class instance is compared to other
2231instances by @racket[equal?], implement the @racket[equal<%>]
2232interface.
2233
2234@definterface[equal<%> ()]{
2235
2236The @racket[equal<%>] interface includes three methods, which are
2237analogous to the functions provided for a structure type with
2238@racket[prop:equal+hash]:
2239
2240@itemize[
2241
2242 @item{@racket[equal-to?] --- Takes two arguments. The first argument
2243 is an object that is an instance of the same class (or a subclass
2244 that does not re-declare its implementation of @racket[equal<%>])
2245 and that is being compared to the target object. The second argument
2246 is an @racket[equal?]-like procedure of two arguments that should be
2247 used for recursive equality testing. The result should be a true
2248 value if the object and the first argument of the method are equal,
2249 @racket[#f] otherwise.}
2250
2251 @item{@racket[equal-hash-code-of] --- Takes one argument, which is a
2252 procedure of one argument that should be used for recursive hash-code
2253 computation. The result should be an exact integer representing the
2254 target object's hash code.}
2255
2256 @item{@racket[equal-secondary-hash-code-of] --- Takes one argument,
2257 which is a procedure of one argument that should be used for
2258 recursive hash-code computation. The result should be an exact
2259 integer representing the target object's secondary hash code.}
2260
2261]
2262
2263The @racket[equal<%>] interface is unusual in that declaring the
2264implementation of the interface is different from inheriting the
2265interface. Two objects can be equal only if they are instances of
2266classes whose most specific ancestor to explicitly implement
2267@racket[equal<%>] is the same ancestor.
2268
2269See @racket[prop:equal+hash] for more information on equality
2270comparisons and hash codes. The @racket[equal<%>] interface is
2271implemented with @racket[interface*] and @racket[prop:equal+hash].}
2272
2273Example:
2274@codeblock|{
2275#lang racket
2276
2277;; Case insensitive words:
2278(define ci-word%
2279  (class* object% (equal<%>)
2280
2281    ;; Initialization
2282    (init-field word)
2283    (super-new)
2284
2285    ;; We define equality to ignore case:
2286    (define/public (equal-to? other recur)
2287      (string-ci=? word (get-field word other)))
2288
2289    ;; The hash codes need to be insensitive to casing as well.
2290    ;; We'll just downcase the word and get its hash code.
2291    (define/public (equal-hash-code-of hash-code)
2292      (hash-code (string-downcase word)))
2293
2294    (define/public (equal-secondary-hash-code-of hash-code)
2295      (hash-code (string-downcase word)))))
2296
2297;; We can create a hash with a single word:
2298(define h (make-hash))
2299(hash-set! h (new ci-word% [word "inconceivable!"]) 'value)
2300
2301;; Lookup into the hash should be case-insensitive, so that
2302;; both of these should return 'value.
2303(hash-ref h (new ci-word% [word "inconceivable!"]))
2304(hash-ref h (new ci-word% [word "INCONCEIVABLE!"]))
2305
2306;; Comparison fails if we use a non-ci-word%:
2307(hash-ref h "inconceivable!" 'i-dont-think-it-means-what-you-think-it-means)
2308}|
2309
2310@; ------------------------------------------------------------------------
2311
2312@section[#:tag "objectserialize"]{Object Serialization}
2313
2314@defform[
2315(define-serializable-class* class-id superclass-expr
2316                                     (interface-expr ...)
2317  class-clause ...)
2318]{
2319
2320Binds @racket[class-id] to a class, where @racket[superclass-expr],
2321the @racket[interface-expr]s, and the @racket[class-clause]s are as in
2322@racket[class*].
2323
2324This form can only be used at the top level, either within a module
2325or outside. The @racket[class-id] identifier is bound to the new
2326class, and @racketidfont{deserialize-info:}@racket[class-id] is also
2327defined; if the definition is within a module, then the latter is
2328provided from a @racket[deserialize-info] submodule via @racket[module+].
2329
2330Serialization for the class works in one of two ways:
2331
2332@itemize[
2333
2334 @item{If the class implements the built-in interface
2335       @racket[externalizable<%>], then an object is serialized by
2336       calling its @racket[externalize] method; the result can be
2337       anything that is serializable (but, obviously, should not be
2338       the object itself). Deserialization creates an instance of the
2339       class with no initialization arguments, and then calls the
2340       object's @racket[internalize] method with the result of
2341       @racket[externalize] (or, more precisely, a deserialized
2342       version of the serialized result of a previous call).
2343
2344       To support this form of serialization, the class must be
2345       instantiable with no initialization arguments. Furthermore,
2346       cycles involving only instances of the class (and other such
2347       classes) cannot be serialized.}
2348
2349 @item{If the class does not implement @racket[externalizable<%>],
2350       then every superclass of the class must be either serializable
2351       or transparent (i.e,. have @racket[#f] as its
2352       inspector). Serialization and deserialization are fully
2353       automatic, and may involve cycles of instances.
2354
2355       To support cycles of instances, deserialization may create an
2356       instance of the call with all fields as the undefined value,
2357       and then mutate the object to set the field
2358       values. Serialization support does not otherwise make an
2359       object's fields mutable.}
2360
2361]
2362
2363In the second case, a serializable subclass can implement
2364@racket[externalizable<%>], in which case the @racket[externalize]
2365method is responsible for all serialization (i.e., automatic
2366serialization is lost for instances of the subclass). In the first
2367case, all serializable subclasses implement
2368@racket[externalizable<%>], since a subclass implements all of the
2369interfaces of its parent class.
2370
2371In either case, if an object is an immediate instance of a subclass
2372(that is not itself serializable), the object is serialized as if it
2373was an immediate instance of the serializable class. In particular,
2374overriding declarations of the @racket[externalize] method are ignored
2375for instances of non-serializable subclasses.}
2376
2377
2378@defform[
2379(define-serializable-class class-id superclass-expr
2380  class-clause ...)
2381]{
2382
2383Like @racket[define-serializable-class*], but without interface
2384expressions (analogous to @racket[class]).}
2385
2386
2387@definterface[externalizable<%> ()]{
2388
2389The @racket[externalizable<%>] interface includes only the
2390@racket[externalize] and @racket[internalize] methods. See
2391@racket[define-serializable-class*] for more information.}
2392
2393@; ------------------------------------------------------------------------
2394
2395@section[#:tag "objectprinting"]{Object Printing}
2396
2397To customize the way that a class instance is printed by
2398@racket[print], @racket[write] and @racket[display], implement the
2399@racket[printable<%>] interface.
2400
2401@defthing[printable<%> interface?]{
2402
2403The @racket[printable<%>] interface includes only the
2404@racket[custom-print], @racket[custom-write], and
2405@racket[custom-display] methods. The @racket[custom-print] method
2406accepts two arguments: the destination port and the current
2407@racket[quasiquote] depth as an exact nonnegative integer. The
2408@racket[custom-write] and @racket[custom-display] methods each accepts
2409a single argument, which is the destination port to @racket[write] or
2410@racket[display] the object.
2411
2412Calls to the @racket[custom-print], @racket[custom-write], or
2413@racket[custom-display] methods are like calls to a procedure attached
2414to a structure type through the @racket[prop:custom-write]
2415property. In particular, recursive printing can trigger an escape from
2416the call.
2417
2418See @racket[prop:custom-write] for more information. The
2419@racket[printable<%>] interface is implemented with
2420@racket[interface*] and @racket[prop:custom-write].}
2421
2422@defthing[writable<%> interface?]{
2423
2424Like @racket[printable<%>], but includes only the
2425@racket[custom-write] and @racket[custom-display] methods.
2426A @racket[print] request is directed to @racket[custom-write].}
2427
2428@; ------------------------------------------------------------------------
2429
2430@section[#:tag "objectutils"]{Object, Class, and Interface Utilities}
2431
2432@defproc[(object? [v any/c]) boolean?]{
2433
2434Returns @racket[#t] if @racket[v] is an object, @racket[#f] otherwise.
2435
2436@examples[#:eval class-eval
2437  (object? (new object%))
2438  (object? object%)
2439  (object? "clam chowder")
2440]}
2441
2442
2443@defproc[(class? [v any/c]) boolean?]{
2444
2445Returns @racket[#t] if @racket[v] is a class, @racket[#f] otherwise.
2446
2447@examples[#:eval class-eval
2448  (class? object%)
2449  (class? (class object% (super-new)))
2450  (class? (new object%))
2451  (class? "corn chowder")
2452]}
2453
2454
2455@defproc[(interface? [v any/c]) boolean?]{
2456
2457Returns @racket[#t] if @racket[v] is an interface, @racket[#f] otherwise.
2458
2459@examples[#:eval class-eval
2460  (interface? (interface () empty cons first rest))
2461  (interface? object%)
2462  (interface? "gazpacho")
2463]}
2464
2465
2466@defproc[(generic? [v any/c]) boolean?]{
2467
2468Returns @racket[#t] if @racket[v] is a @tech{generic}, @racket[#f] otherwise.
2469
2470@examples[#:eval class-eval
2471  (define c%
2472    (class object%
2473      (super-new)
2474      (define/public (m x)
2475        (+ 3.14 x))))
2476
2477  (generic? (generic c% m))
2478  (generic? c%)
2479  (generic? "borscht")
2480]}
2481
2482
2483@defproc[(object=? [a object?] [b object?]) boolean?]{
2484
2485Determines whether @racket[a] and @racket[b] were returned from
2486the same call to @racket[new] or not. If the two objects
2487have fields, this procedure determines whether mutating a field
2488of one would change that field in the other.
2489
2490This procedure is similar in spirit to
2491@racket[eq?] but also works properly with contracts
2492(and has a stronger guarantee).
2493
2494@examples[#:eval class-ctc-eval
2495  (define obj-1 (new object%))
2496  (define obj-2 (new object%))
2497  (define/contract obj-3 (object/c) obj-1)
2498
2499  (object=? obj-1 obj-1)
2500  (object=? obj-1 obj-2)
2501  (object=? obj-1 obj-3)
2502
2503  (eq? obj-1 obj-1)
2504  (eq? obj-1 obj-2)
2505  (eq? obj-1 obj-3)
2506]}
2507
2508
2509@defproc[(object-or-false=? [a (or/c object? #f)] [b (or/c object? #f)]) boolean?]{
2510
2511Like @racket[object=?], but accepts @racket[#f] for either argument and
2512returns @racket[#t] if both arguments are @racket[#f].
2513
2514@examples[#:eval class-ctc-eval
2515   (object-or-false=? #f (new object%))
2516   (object-or-false=? (new object%) #f)
2517   (object-or-false=? #f #f)
2518   ]
2519
2520@history[#:added "6.1.1.8"]}
2521
2522@defproc[(object=-hash-code [o object?]) fixnum?]{
2523 Returns the hash code for @racket[o] that corresponds to
2524 the equality relation @racket[object=?].
2525
2526@history[#:added "7.1.0.6"]}
2527
2528@defproc[(object->vector [object object?] [opaque-v any/c #f]) vector?]{
2529
2530Returns a vector representing @racket[object] that shows its
2531inspectable fields, analogous to @racket[struct->vector].
2532
2533@examples[#:eval class-eval
2534  (object->vector (new object%))
2535  (object->vector (new (class object%
2536                         (super-new)
2537                         (field [x 5] [y 10]))))
2538]}
2539
2540
2541@defproc[(class->interface [class class?]) interface?]{
2542
2543Returns the interface implicitly defined by @racket[class].
2544
2545@examples[#:eval class-eval
2546  (class->interface object%)
2547]}
2548
2549
2550@defproc[(object-interface [object object?]) interface?]{
2551
2552Returns the interface implicitly defined by the class of
2553@racket[object].
2554
2555@examples[#:eval class-eval
2556  (object-interface (new object%))
2557]}
2558
2559
2560@defproc[(is-a? [v any/c] [type (or/c interface? class?)]) boolean?]{
2561
2562Returns @racket[#t] if @racket[v] is an instance of a class
2563@racket[type] or a class that implements an interface @racket[type],
2564@racket[#f] otherwise.
2565
2566@examples[#:eval class-eval
2567  (define point<%> (interface () get-x get-y))
2568  (define 2d-point%
2569    (class* object% (point<%>)
2570      (super-new)
2571      (field [x 0] [y 0])
2572      (define/public (get-x) x)
2573      (define/public (get-y) y)))
2574
2575  (is-a? (new 2d-point%) 2d-point%)
2576  (is-a? (new 2d-point%) point<%>)
2577  (is-a? (new object%) 2d-point%)
2578  (is-a? (new object%) point<%>)
2579]}
2580
2581
2582@defproc[(subclass? [v any/c] [cls class?]) boolean?]{
2583
2584Returns @racket[#t] if @racket[v] is a class derived from (or equal
2585to) @racket[cls], @racket[#f] otherwise.
2586
2587@examples[#:eval class-eval
2588  (subclass? (class object% (super-new)) object%)
2589  (subclass? object% (class object% (super-new)))
2590  (subclass? object% object%)
2591]}
2592
2593
2594@defproc[(implementation? [v any/c] [intf interface?]) boolean?]{
2595
2596Returns @racket[#t] if @racket[v] is a class that implements
2597@racket[intf], @racket[#f] otherwise.
2598
2599@examples[#:eval class-eval
2600  (define i<%> (interface () go))
2601  (define c%
2602    (class* object% (i<%>)
2603      (super-new)
2604      (define/public (go) 'go)))
2605
2606  (implementation? c% i<%>)
2607  (implementation? object% i<%>)
2608]}
2609
2610
2611@defproc[(interface-extension? [v any/c] [intf interface?]) boolean?]{
2612
2613Returns @racket[#t] if @racket[v] is an interface that extends
2614@racket[intf], @racket[#f] otherwise.
2615
2616@examples[#:eval class-eval
2617  (define point<%> (interface () get-x get-y))
2618  (define colored-point<%> (interface (point<%>) color))
2619
2620  (interface-extension? colored-point<%> point<%>)
2621  (interface-extension? point<%> colored-point<%>)
2622  (interface-extension? (interface () get-x get-y get-z) point<%>)
2623]}
2624
2625
2626@defproc[(method-in-interface? [sym symbol?] [intf interface?]) boolean?]{
2627
2628Returns @racket[#t] if @racket[intf] (or any of its ancestor
2629interfaces) includes a member with the name @racket[sym], @racket[#f]
2630otherwise.
2631
2632@examples[#:eval class-eval
2633  (define i<%> (interface () get-x get-y))
2634  (method-in-interface? 'get-x i<%>)
2635  (method-in-interface? 'get-z i<%>)
2636]}
2637
2638
2639@defproc[(interface->method-names [intf interface?]) (listof symbol?)]{
2640
2641Returns a list of symbols for the method names in @racket[intf],
2642including methods inherited from superinterfaces, but not including
2643methods whose names are local (i.e., declared with
2644@racket[define-local-member-name]).
2645
2646@examples[#:eval class-eval
2647  (define i<%> (interface () get-x get-y))
2648  (interface->method-names i<%>)
2649]}
2650
2651
2652@defproc[(object-method-arity-includes? [object object?] [sym symbol?] [cnt exact-nonnegative-integer?])
2653         boolean?]{
2654
2655Returns @racket[#t] if @racket[object] has a method named @racket[sym]
2656that accepts @racket[cnt] arguments, @racket[#f] otherwise.
2657
2658@examples[#:eval class-eval
2659(define c%
2660  (class object%
2661    (super-new)
2662    (define/public (m x [y 0])
2663      (+ x y))))
2664
2665(object-method-arity-includes? (new c%) 'm 1)
2666(object-method-arity-includes? (new c%) 'm 2)
2667(object-method-arity-includes? (new c%) 'm 3)
2668(object-method-arity-includes? (new c%) 'n 1)
2669]}
2670
2671
2672@defproc[(field-names [object object?]) (listof symbol?)]{
2673
2674Returns a list of all of the names of the fields bound in
2675@racket[object], including fields inherited from superinterfaces, but
2676not including fields whose names are local (i.e., declared with
2677@racket[define-local-member-name]).
2678
2679@examples[#:eval class-eval
2680  (field-names (new object%))
2681  (field-names (new (class object% (super-new) (field [x 0] [y 0]))))
2682]}
2683
2684
2685@defproc[(object-info [object object?]) (values (or/c class? #f) boolean?)]{
2686
2687Returns two values, analogous to the return
2688values of @racket[struct-info]:
2689@itemize[
2690
2691  @item{@racket[_class]: a class or @racket[#f]; the result is
2692  @racket[#f] if the current inspector does not control any class for
2693  which the @racket[object] is an instance.}
2694
2695  @item{@racket[_skipped?]: @racket[#f] if the first result corresponds
2696  to the most specific class of @racket[object], @racket[#t]
2697  otherwise.}
2698
2699]}
2700
2701
2702@defproc[(class-info [class class?])
2703         (values symbol?
2704                 exact-nonnegative-integer?
2705                 (listof symbol?)
2706                 (any/c exact-nonnegative-integer? . -> . any/c)
2707                 (any/c exact-nonnegative-integer? any/c . -> . any/c)
2708                 (or/c class? #f)
2709                 boolean?)]{
2710
2711Returns seven values, analogous to the return
2712values of @racket[struct-type-info]:
2713
2714@itemize[
2715
2716  @item{@racket[_name]: the class's name as a symbol;}
2717
2718  @item{@racket[_field-cnt]: the number of fields (public and private)
2719   defined by the class;}
2720
2721  @item{@racket[_field-name-list]: a list of symbols corresponding to the
2722  class's public fields; this list can be larger than @racket[_field-cnt]
2723  because it includes inherited fields;}
2724
2725  @item{@racket[_field-accessor]: an accessor procedure for obtaining
2726  field values in instances of the class; the accessor takes an
2727  instance and a field index between @racket[0] (inclusive)
2728  and @racket[_field-cnt] (exclusive);}
2729
2730  @item{@racket[_field-mutator]: a mutator procedure for modifying
2731  field values in instances of the class; the mutator takes an
2732  instance, a field index between @racket[0] (inclusive)
2733  and @racket[_field-cnt] (exclusive), and a new field value;}
2734
2735  @item{@racket[_super-class]: a class for the most specific ancestor of
2736   the given class that is controlled by the current inspector,
2737   or @racket[#f] if no ancestor is controlled by the current
2738   inspector;}
2739
2740  @item{@racket[_skipped?]: @racket[#f] if the sixth result is the most
2741   specific ancestor class, @racket[#t] otherwise.}
2742
2743]}
2744
2745@defstruct[(exn:fail:object exn:fail) ()]{
2746
2747Raised for @racket[class]-related failures, such as attempting to call
2748a method that is not supplied by an object.
2749
2750}
2751
2752@defproc[(class-seal [class class?]
2753                     [key symbol?]
2754                     [unsealed-inits (listof symbol?)]
2755                     [unsealed-fields (listof symbol?)]
2756                     [unsealed-methods (listof symbol?)]
2757                     [inst-proc (-> class? any)]
2758                     [member-proc (-> class? (listof symbol?) any)])
2759         class?]{
2760
2761Adds a seal to a given class keyed with the symbol @racket[key]. The
2762given @racket[unsealed-inits], @racket[unsealed-fields], and
2763@racket[unsealed-methods] list corresponding class members that are
2764unaffected by sealing.
2765
2766When a class has any seals, the @racket[inst-proc] procedure is called
2767on instantiation (normally, this is used to raise an error on
2768instantiation) and the @racket[member-proc] function is called
2769(again, this is normally used to raise an error) when a subclass
2770attempts to add class members that are not listed in the unsealed lists.
2771
2772The @racket[inst-proc] is called with the class value on which an
2773instantiation was attempted. The @racket[member-proc] is called with
2774the class value and the list of initialization argument, field, or
2775method names.
2776}
2777
2778@defproc[(class-unseal [class class?]
2779                       [key symbol?]
2780                       [wrong-key-proc (-> class? any)])
2781         class?]{
2782
2783Removes a seal on a class that has been previously sealed with the
2784@racket[class-seal] function and the given @racket[key].
2785
2786If the unseal removed all of the seals in the class, the class
2787value can be instantiated or subclassed freely. If the given
2788class value does not contain or any seals or does not contain
2789any seals with the given key, the @racket[wrong-key-proc] function
2790is called with the class value.
2791}
2792
2793@; ----------------------------------------------------------------------
2794
2795@include-section["surrogate.scrbl"]
2796
2797@close-eval[class-eval]
2798