On this page:
4.1 Special forms
class
define/  public
define/  override
define/  pubment
define/  augment
define/  private
init
init-field
field
inherit-field
init-rest
public
pubment
override
augment
private
inherit
4.2 Types
Class
Class  Top
Object
Instance
6.6

4 Typed Classes

Warning: the features described in this section are experimental and may not work correctly. Some of the features will change by the next release. In particular, typed-untyped interaction for classes will not be backwards compatible so do not rely on the current semantics.

Typed Racket provides support for object-oriented programming with the classes and objects provided by the racket/class library.

4.1 Special forms

 (require typed/racket/class) package: typed-racket-lib

The special forms below are provided by the typed/racket/class and typed/racket modules but not by typed/racket/base. The typed/racket/class module additional provides all other bindings from racket/class.

syntax

(class superclass-expr
  maybe-type-parameters
  class-clause ...)
 
class-clause = (inspect inspector-expr)
  | (init init-decl ...)
  | (init-field init-decl ...)
  | (init-rest id/type)
  | (field field-decl ...)
  | (inherit-field field-decl ...)
  | (public maybe-renamed/type ...)
  | (pubment maybe-renamed/type ...)
  | (override maybe-renamed/type ...)
  | (augment maybe-renamed/type ...)
  | (private id/type ...)
  | (inherit id ...)
  | method-definition
  | definition
  | expr
  | (begin class-clause ...)
     
maybe-type-parameters = 
  | #:forall (type-variable ...)
  | #:∀ (type-variable ...)
     
init-decl = id/type
  | [renamed]
  | [renamed : type-expr]
  | [maybe-renamed default-value-expr]
  | [maybe-renamed : type-expr default-value-expr]
     
field-decl = (maybe-renamed default-value-expr)
  | (maybe-renamed : type-expr default-value-expr)
     
id/type = id
  | [id : type-expr]
     
maybe-renamed/type = maybe-renamed
  | [maybe-renamed : type-expr]
     
maybe-renamed = id
  | renamed
     
renamed = (internal-id external-id)
Produces a class with type annotations that allows Typed Racket to type-check the methods, fields, and other clauses in the class.

The meaning of the class clauses are the same as in the class form from the racket/class library with the exception of the additional optional type annotations. Additional class clause forms from class that are not listed in the grammar above are not currently supported in Typed Racket.

Examples:
> (define fish%
    (class object%
      (init [size : Real])
  
      (: current-size Real)
      (define current-size size)
  
      (super-new)
  
      (: get-size (-> Real))
      (define/public (get-size)
        current-size)
  
      (: grow (Real -> Void))
      (define/public (grow amt)
        (set! current-size (+ amt current-size)))
  
      (: eat ((Object [get-size (-> Real)]) -> Void))
      (define/public (eat other-fish)
        (grow (send other-fish get-size)))))
> (define dory (new fish% [size 5.5]))

Within a typed class form, one of the class clauses must be a call to super-new. Failure to call super-new will result in a type error. In addition, dynamic uses of super-new (e.g., calling it in a separate function within the dynamic extent of the class form’s clauses) are restricted.

Example:
> (class object%
    ; Note the missing `super-new`
    (init-field [x : Real 0] [y : Real 0]))

racket/collects/racket/private/class-undef.rkt:46:6: Type

Checker: ill-formed typed class;

 must call `super-new' at the top-level of the class

  in: (#%expression (#%app compose-class (quote eval:4:0)

object% (#%app list) (#%app current-inspector) (quote #f)

(quote #f) (quote 2) (quote (x y)) (quote ()) (quote ())

(quote ()) (quote ()) (quote ()) (quote ()) (quote ())

(quote ()) (quote ()) (quote ()...

If any identifier with an optional type annotation is left without an annotation, the type-checker will assume the type Any (or Procedure for methods) for that identifier.

Examples:
> (define point%
    (class object%
      (super-new)
      (init-field x y)))
> point%

- : (Class (init (x Any) (y Any)) (field (x Any) (y Any)))

#<class:point%>

When type-variable is provided, the class is parameterized over the given type variables. These type variables are in scope inside the body of the class. The resulting class can be instantiated at particular types using inst.

Examples:
> (define cons%
    (class object%
      #:forall (X Y)
      (super-new)
      (init-field [car : X] [cdr : Y])))
> cons%

- : (All (X Y) (Class (init (car X) (cdr Y)) (field (car X) (cdr Y))))

#<class:cons%>

> (new (inst cons% Integer String) [car 5] [cdr "foo"])

- : (Object (field (car Integer) (cdr String)))

(object:cons% ...)

Initialization arguments may be provided by-name using the new form, by-position using the make-object form, or both using the instantiate form.

As in ordinary Racket classes, the order in which initialization arguments are declared determines the order of initialization types in the class type.

Furthermore, a class may also have a typed init-rest clause, in which case the class constructor takes an unbounded number of arguments by-position. The type of the init-rest clause must be either a List type, Listof type, or any other list type.

Examples:
> (define point-copy%
    ; a point% with a copy constructor
    (class object%
      (super-new)
      (init-rest [rst : (U (List Integer Integer)
                           (List (Object (field [x Integer]
                                                [y Integer]))))])
      (field [x : Integer 0] [y : Integer 0])
      (match rst
        [(list (? integer? *x) *y)
         (set! x *x) (set! y *y)]
        [(list (? (negate integer?) obj))
         (set! x (get-field x obj))
         (set! y (get-field y obj))])))
> (define p1 (make-object point-copy% 1 2))
> (make-object point-copy% p1)

- : (Object (field (x Integer) (y Integer)))

(object:point-copy% ...)

syntax

(define/public id expr)

(define/public (id . formals) body ...+)
Like define/public from racket/class, but uses the binding of define from Typed Racket. The formals may specify type annotations as in define.

syntax

(define/override id expr)

(define/override (id . formals) body ...+)
Like define/override from racket/class, but uses the binding of define from Typed Racket. The formals may specify type annotations as in define.

syntax

(define/pubment id expr)

(define/pubment (id . formals) body ...+)
Like define/pubment from racket/class, but uses the binding of define from Typed Racket. The formals may specify type annotations as in define.

syntax

(define/augment id expr)

(define/augment (id . formals) body ...+)
Like define/augment from racket/class, but uses the binding of define from Typed Racket. The formals may specify type annotations as in define.

syntax

(define/private id expr)

(define/private (id . formals) body ...+)
Like define/private from racket/class, but uses the binding of define from Typed Racket. The formals may specify type annotations as in define.

syntax

(init init-decl ...)

syntax

(init-field init-decl ...)

syntax

(field field-decl ...)

syntax

(inherit-field field-decl ...)

syntax

(init-rest id/type)

syntax

(public maybe-renamed/type ...)

syntax

(pubment maybe-renamed/type ...)

syntax

(override maybe-renamed/type ...)

syntax

(augment maybe-renamed/type ...)

syntax

(private id/type ...)

syntax

(inherit maybe-renamed/type ...)

These forms are mostly equivalent to the forms of the same names from the racket/class library and will expand to them. However, they also allow the initialization argument, field, or method names to be annotated with types as described above for the class form.

4.2 Types

syntax

(Class class-type-clause ...)

 
class-type-clause = name+type
  | (init init-type ...)
  | (init-field init-type ...)
  | (init-rest name+type)
  | (field name+type ...)
  | (augment name+type ...)
  | #:implements type-alias-id
  | #:implements/inits inits-id
  | #:row-var row-var-id
     
init-type = name+type
  | [id type #:optional]
     
name+type = [id type]
The type of a class with the given initialization argument, method, and field types.

Example:
> (: food% (Class (init [liquid? Boolean])
                  (field [nutrition Integer])
                  [get-nutrition (-> Integer)]))

The types of methods are provided either without a keyword, in which case they correspond to public methods, or with the augment keyword, in which case they correspond to a method that can be augmented.

An initialization argument type specifies a name and type and optionally a #:optional keyword. An initialization argument type with #:optional corresponds to an argument that does not need to be provided at object instantiation.

Example:
> (: drink% (Class (init [color String]
                         [carbonated? Boolean]
                         [viscosity Positive-Real #:optional])))

The order of initialization arguments in the type is significant, because it determines the types of by-position arguments for use with make-object and instantiate. A given Class type may also only contain a single init-rest clause.

Examples:
> (define drink%
    (class object%
      (super-new)
      ; The order of `color' and `carbonated?' cannot be swapped
      (init color carbonated? [viscosity 1.002])))
; The order of initialization matches the order in the type
> (make-object drink% "purple" #t)

- : (Object)

(object:drink% ...)

When type-alias-id is provided, the resulting class type includes all of the method and field types from the specified type alias (which must be an alias for a class type). This is intended to allow a type for a subclass to include parts of its parent class type. The initialization argument types of the parent, however, are not included because a subclass does not necessarily share the same initialization arguments as its parent class.

Initialization argument types can be included from the parent by providing inits-id with the #:implements/inits keyword. This is identical to the #:implements clause except for the initialization argument behavior. Only a single #:implements/inits clause may be provided for a single Class type. The initialization arguments copied from the parent type are appended to the initialization arguments specified via the init and init-field clauses.

Multiple #:implements clauses may be provided for a single class type. The types for the #:implements clauses are merged in order and the last type for a given method name or field is used (the types in the Class type itself takes precedence).

Examples:
> (define-type Point<%> (Class (field [x Real] [y Real])))
> (: colored-point% (Class #:implements Point<%>
                           (field [color String])))

When row-var-id is provided, the class type is an abstract type that is row polymorphic. A row polymorphic class type can be instantiated at a specific row using inst. Only a single #:row-var clause may appear in a class type.

syntax

ClassTop

The supertype of all class types. A value of this type cannot be used for subclassing, object creation, or most other class functions. Its primary use is for reflective operations such as is-a?.

syntax

(Object object-type-clause ...)

 
object-type-clause = name+type
  | (field name+type ...)
The type of an object with the given field and method types.

Examples:
> (new object%)

- : (Object)

(object)

> (new (class object% (super-new) (field [x : Real 0])))

- : (Object (field (x Real)))

(object:eval:20:0 ...)

syntax

(Instance class-type-expr)

The type of an object that corresponds to class-type-expr.

This is the same as an Object type that has all of the method and field types from class-type-expr. The types for the augment and init clauses in the class type are ignored.

Examples:
> (define-type Point% (Class (init-field [x Integer] [y Integer])))
> (: a-point (Instance Point%))
> (define a-point
    (new (class object%
           (super-new)
           (init-field [x : Integer 0] [y : Integer 0]))))