On this page:
Any
One
EOF
1.5Control
->
->*
Top
Bot
U
All
Rec
Imp
8.18
top
up

1Type ReferenceπŸ”— i

type

Any

Any Racket value. All other types are subtypes of Any .

type

AnyValues

Any number of Racket values of any type.

type

Nothing

The empty type. No values inhabit this type, and any expression of this type will not evaluate to a value.

1.1Base TypesπŸ”— i

1.1.1Numeric TypesπŸ”— i

These types represent the hierarchy of numbers of Racket. The diagram below shows the relationships between the types in the hierarchy.

[画像:image]

The regions with a solid border are layers of the numeric hierarchy corresponding to sets of numbers such as integers or rationals. Layers contained within another are subtypes of the layer containing them. For example, Exact-Rational is a subtype of Exact-Number .

The Real layer is also divided into positive and negative types (shown with a dotted line). The Integer layer is subdivided into several fixed-width integers types, detailed later in this section.

type

Number

type

Complex

Number and Complex are synonyms. This is the most general numeric type, including all Racket numbers, both exact and inexact, including complex numbers.

type

Integer

Includes Racket’s exact integers and corresponds to the exact-integer? predicate. This is the most general type that is still valid for indexing and other operations that require integral values.

type

Float

type

Flonum

Includes Racket’s double-precision (default) floating-point numbers and corresponds to the flonum? predicate. This type excludes single-precision floating-point numbers.

Includes Racket’s single-precision floating-point numbers and corresponds to the single-flonum? predicate. This type excludes double-precision floating-point numbers.

Includes all of Racket’s floating-point numbers, both single- and double-precision.

Includes Racket’s exact rationals, which include fractions and exact integers.

type

Real

Includes all of Racket’s real numbers, which include both exact rationals and all floating-point numbers. This is the most general type for which comparisons (e.g. < ) are defined.

These types correspond to Racket’s complex numbers.

Changed in version 1.7 of package typed-racket-lib: Added Imaginary , Inexact-Complex , Exact-Complex , Exact-Imaginary , Inexact-Imaginary .

The above types can be subdivided into more precise types if you want to enforce tighter constraints. Typed Racket provides types for the positive, negative, non-negative and non-positive subsets of the above types (where applicable).

type

Natural

type

Zero

type

Float-Zero

type

Float-Nan

type

Flonum-Nan

type

Real-Zero

Natural and Exact-Nonnegative-Integer are synonyms. So are the integer and exact-integer types, and the float and flonum types. Zero includes only the integer 0. Real-Zero includes exact 0 and all the floating-point zeroes.

These types are useful when enforcing that values have a specific sign. However, programs using them may require additional dynamic checks when the type-checker cannot guarantee that the sign constraints will be respected.

In addition to being divided by sign, integers are further subdivided into range-bounded types. The relationships between most of the range-bounded types are shown in this diagram:

[画像:image]

Like the previous diagram, types nested inside of another in the diagram are subtypes of its containing types.

One includes only the integer 1. Byte includes numbers from 0 to 255. Index is bounded by 0 and by the length of the longest possible Racket vector. Fixnum includes all numbers represented by Racket as machine integers. For the latter two families, the sets of values included in the types are architecture-dependent, but typechecking is architecture-independent.

These types are useful to enforce bounds on numeric values, but given the limited amount of closure properties these types offer, dynamic checks may be needed to check the desired bounds at runtime.

Examples:
> 7

- : Integer [more precisely: Positive-Byte]

7

> 8.3

- : Flonum [more precisely: Positive-Float-No-NaN]

8.3

> (/ 83)

- : Exact-Rational [more precisely: Positive-Exact-Rational]

8/3

> 0

- : Integer [more precisely: Zero]

0

> -12

- : Integer [more precisely: Negative-Fixnum]

-12

> 3+4i

- : Exact-Number

3+4i

80-bit extflonum types, for the values operated on by racket/extflonum exports. These are not part of the numeric tower.

1.1.2Other Base TypesπŸ”— i

type

Boolean

type

True

type

False

type

String

type

Keyword

type

Symbol

type

Char

type

Void

type

Input-Port

type

Port

type

Path

type

Regexp

type

PRegexp

type

Bytes

type

Namespace

type

Null

type

EOF

type

Undefined

type

Read-Table

type

Custodian

type

Inspector

type

UDP-Socket

type

Logger

type

Log-Level

type

Thread

type

Subprocess

type

Place

type

Semaphore

type

FSemaphore

These types represent primitive Racket data.

Examples:
> #t

- : True

#t

> #f

- : False

#f

> "hello"

- : String

"hello"

- : Input-Port

#<input-port:string>

- : Output-Port

#<output-port:string>

> (string->path "/")

- : Path

#<path:/>

> #rx"a*b*"

- : Regexp

#rx"a*b*"

> #px"a*b*"

- : PRegexp

#px"a*b*"

> '#"bytes"

- : Bytes

#"bytes"

- : Namespace

#<namespace>

> #\b

- : Char

#\b

> (thread (lambda ()(add1 7)))

- : Thread

#<thread>

The union of the Path and String types. Note that this does not match exactly what the predicate path-string? recognizes. For example, strings that contain the character #\nul have the type Path-String but path-string? returns #f for those strings. For a complete specification of which strings path-string? accepts, see its documentation.

1.2Singleton TypesπŸ”— i

Some kinds of data are given singleton types by default. In particular, booleans, symbols, and keywords have types which consist only of the particular boolean, symbol, or keyword. These types are subtypes of Boolean , Symbol and Keyword , respectively.

Examples:
> #t

- : True

#t

> '#:foo

- : '#:foo

'#:foo

> 'bar

- : 'bar

'bar

1.3Base Type Constructors and SupertypesπŸ”— i

type constructor

( Pairof st)

Returns a pair type containing s as the car and t as the cdr

Examples:
> (cons 12)

- : (Pairof One Positive-Byte)

'(1 . 2)

> (cons 1"one")

- : (Pairof One String)

'(1 . "one")

type constructor

( Listof t)

Returns the type of a homogeneous list of t

type constructor

( List t...)

Returns a list type with one element, in order, for each type provided to the List type constructor.

type constructor

(List t...trest...bound)

Returns the type of a list with one element for each of the ts, plus a sequence of elements corresponding to trest, where bound must be an identifier denoting a type variable bound with ... .

type constructor

( List* tt1...s)

Is equivalent to (Pairof t(List* t1... s)). (List* s) is equivalent to s itself.

Examples:
> (list 'a'b'c)

- : (List 'a 'b 'c)

'(a b c)

> (plambda: (a... )([sym: Symbol ]boxes: (Boxof a)... a)
(ann (cons symboxes)(List Symbol (Boxof a)... a)))

- : (All (a ...)

(-> Symbol (Boxof a) ... a (Pairof Symbol (List (Boxof a) ... a))))

#<procedure>

> (map symbol->string (list 'a'b'c))

- : (Pairof String (Listof String))

'("a" "b" "c")

type constructor

( MListof t)

Returns the type of a homogeneous mutable list of t.

type constructor

( MPairof tu)

Returns the type of a Mutable pair of t and u.

type constructor

( TreeListof t)

Returns the type of treelist of t

type

MPairTop

Is the type of a mutable pair with unknown element types and is the supertype of all mutable pair types. This type typically appears in programs via the combination of occurrence typing and mpair? .

Example:
> (lambda: ([x: Any ])(if (mpair? x)x(error "not an mpair!")))

- : (-> Any MPairTop)

#<procedure>

type constructor

( Boxof t)

Returns the type of a box of t

Example:
> (box "hello world")

- : (Boxof String)

'#&"hello world"

type

BoxTop

Is the type of a box with an unknown element type and is the supertype of all box types. Only read-only box operations (e.g. unbox ) are allowed on values of this type. This type typically appears in programs via the combination of occurrence typing and box? .

Example:
> (lambda: ([x: Any ])(if (box? x)x(error "not a box!")))

- : (-> Any BoxTop)

#<procedure>

type constructor

( Vectorof t)

Returns the type of a homogeneous vector list of t (mutable or immutable).

type constructor

( Immutable-Vectorof t)

Returns the type of a homogeneous immutable vector of t.

Added in version 1.9 of package typed-racket-lib.

type constructor

( Mutable-Vectorof t)

Returns the type of a homogeneous mutable vector of t.

Added in version 1.9 of package typed-racket-lib.

type constructor

( Vector t...)

Returns the type of a mutable or immutable vector with one element, in order, for each type provided to the Vector type constructor.

Example:
> (ann (vector 1'A)(Vector Fixnum 'A))

- : (U (Immutable-Vector Fixnum 'A) (Mutable-Vector Fixnum 'A))

'#(1 A)

type constructor

( Immutable-Vector t...)

Similar to (Vector t... ), but for immutable vectors.

Example:

- : (Immutable-Vector One Positive-Byte Positive-Byte)

'#(1 2 3)

Added in version 1.9 of package typed-racket-lib.

type constructor

( Mutable-Vector t...)

Similar to (Vector t... ), but for mutable vectors.

Example:
> (vector 123)

- : (Mutable-Vector Integer Integer Integer)

'#(1 2 3)

Added in version 1.9 of package typed-racket-lib.

type

FlVector

Example:
> (flvector1.02.03.0)

- : FlVector

(flvector 1.0 2.0 3.0)

Example:
> (extflvector1.0t02.0t03.0t0)

- : ExtFlVector

#<extflvector>

type

FxVector

Example:
> (fxvector123)

- : FxVector

(fxvector 1 2 3)

type

VectorTop

Is the type of a vector with unknown length and element types and is the supertype of all vector types. Only read-only vector operations (e.g. vector-ref ) are allowed on values of this type. This type typically appears in programs via the combination of occurrence typing and vector? .

Example:
> (lambda: ([x: Any ])(if (vector? x)x(error "not a vector!")))

- : (-> Any VectorTop)

#<procedure>

Is the type of a mutable vector with unknown length and element types.

type constructor

( HashTable kv)

Returns the type of a mutable or immutable hash table with key type k and value type v.

Example:
> (ann (make-hash '((a. 1)(b. 2)))(HashTable Symbol Integer ))

- : (HashTable Symbol Integer)

'#hash((a . 1) (b . 2))

type constructor

( Immutable-HashTable kv)

Returns the type of an immutable hash table with key type k and value type v.

Example:
> #hash((a. 1)(b. 2))

- : (Immutable-HashTable Symbol Integer)

'#hash((a . 1) (b . 2))

Added in version 1.8 of package typed-racket-lib.

type constructor

( Mutable-HashTable kv)

Returns the type of a mutable hash table that holds keys strongly (see Weak Boxes) with key type k and value type v.

Example:
> (make-hash '((a. 1)(b. 2)))

- : (Mutable-HashTable Symbol Integer)

'#hash((a . 1) (b . 2))

Added in version 1.8 of package typed-racket-lib.

type constructor

( Weak-HashTable kv)

Returns the type of a mutable hash table that holds keys weakly with key type k and value type v.

Example:
> (make-weak-hash '((a. 1)(b. 2)))

- : (Weak-HashTable Symbol Integer)

'#hash((a . 1) (b . 2))

Added in version 1.8 of package typed-racket-lib.

Is the type of a hash table with unknown key and value types and is the supertype of all hash table types. Only read-only hash table operations (e.g. hash-ref ) are allowed on values of this type. This type typically appears in programs via the combination of occurrence typing and hash? .

Example:
> (lambda: ([x: Any ])(if (hash? x)x(error "not a hash table!")))

- : (-> Any HashTableTop)

#<procedure>

Is the type of a mutable hash table that holds keys strongly with unknown key and value types.

Is the type of a mutable hash table that holds keys weakly with unknown key and value types.

type constructor

( Setof t)

Returns the type of a hash set of t. This includes custom hash sets, but not mutable hash set or sets that are implemented using gen:set .

Example:
> (set 0123)

- : (Setof Byte)

(set 0 1 2 3)

Example:
> (seteq 0123)

- : (Setof Byte)

(seteq 0 1 2 3)

type constructor

( Channelof t)

Returns the type of a channel on which only ts can be sent.

Example:

- : (Channelof Symbol)

#<channel>

type

ChannelTop

Is the type of a channel with unknown message type and is the supertype of all channel types. This type typically appears in programs via the combination of occurrence typing and channel? .

Example:
> (lambda: ([x: Any ])(if (channel? x)x(error "not a channel!")))

- : (-> Any ChannelTop)

#<procedure>

type constructor

( Async-Channelof t)

Returns the type of an asynchronous channel on which only ts can be sent.

Examples:
> (require typed/racket/async-channel)

- : (Async-Channelof Symbol)

#<async-channel>

Added in version 1.1 of package typed-racket-lib.

Is the type of an asynchronous channel with unknown message type and is the supertype of all asynchronous channel types. This type typically appears in programs via the combination of occurrence typing and async-channel? .

Examples:
> (require typed/racket/async-channel)
> (lambda: ([x: Any ])(if (async-channel? x)x(error "not an async-channel!")))

- : (-> Any Async-ChannelTop)

#<procedure>

Added in version 1.1 of package typed-racket-lib.

type constructor

( Parameterof t)

Returns the type of a parameter of t. If two type arguments are supplied, the first is the type the parameter accepts, and the second is the type returned.

Examples:

- : (Parameterof Input-Port)

#<procedure:current-input-port>

- : (Parameterof Path-String Path)

#<procedure:current-directory>

type constructor

( Promise t)

Returns the type of promise of t.

Example:
> (delay 3)

- : (Promise Positive-Byte)

#<promise:eval:52:0>

type constructor

( Futureof t)

Returns the type of future which produce a value of type t when touched.

type constructor

( Sequenceof t...)

Returns the type of sequence that produces (Values t... ) on each iteration. E.g., (Sequenceof ) is a sequence which produces no values, (Sequenceof String ) is a sequence of strings, (Sequenceof Number String ) is a sequence which produces two values—a number and a string—on each iteration, etc.

Is the type of a sequence with unknown element type and is the supertype of all sequences. This type typically appears in programs via the combination of ocurrence typing ang sequence? .

Example:
> (lambda: ([x: Any ])(if (sequence? x)x(error "not a sequence!")))

- : (-> Any SequenceTop)

#<procedure>

Added in version 1.10 of package typed-racket-lib.

type constructor

( Custodian-Boxof t)

Returns the type of custodian box of t.

type constructor

( Thread-Cellof t)

Returns the type of thread cell of t.

Is the type of a thread cell with unknown element type and is the supertype of all thread cell types. This type typically appears in programs via the combination of occurrence typing and thread-cell? .

Example:
> (lambda: ([x: Any ])(if (thread-cell? x)x(error "not a thread cell!")))

- : (-> Any Thread-CellTop)

#<procedure>

type constructor

( Weak-Boxof t)

Returns the type for a weak box whose value is of type t.

Examples:

- : (Weak-Boxof Integer)

#<weak-box>

- : (U False Integer)

5

Is the type of a weak box with an unknown element type and is the supertype of all weak box types. This type typically appears in programs via the combination of occurrence typing and weak-box? .

Example:
> (lambda: ([x: Any ])(if (weak-box? x)x(error "not a box!")))

- : (-> Any Weak-BoxTop)

#<procedure>

type constructor

( Ephemeronof t)

Returns the type of an ephemeron whose value is of type t.

type constructor

( Evtof t)

Examples:

- : (Rec x (Evtof x))

#<always-evt>

- : (Evtof Void)

#<system-idle-evt>

> (ann (thread (λ ()(displayln "hello world")))(Evtof Thread ))

- : (Evtof Thread)

hello world

#<thread>

1.4Syntax ObjectsπŸ”— i

The following type constructors and types respectively create and represent syntax objects and their content.

type constructor

( Syntaxof t)

Returns the type of syntax object with content of type t. Applying syntax-e to a value of type (Syntaxof t) produces a value of type t.

type

Identifier

A syntax object containing a symbol. Equivalent to (Syntaxof Symbol ).

type

Syntax

A syntax object containing only symbols, keywords, strings, byte strings, characters, booleans, numbers, boxes containing Syntax , vectors of Syntax , or (possibly improper) lists of Syntax . Equivalent to (Syntaxof Syntax-E ).

type

Syntax-E

The content of syntax objects of type Syntax . Applying syntax-e to a value of type Syntax produces a value of type Syntax-E .

type constructor

( Sexpof t)

Returns the recursive union of t with symbols, keywords, strings, byte strings, characters, booleans, numbers, boxes, vectors, and (possibly improper) lists.

type

Sexp

Applying syntax->datum to a value of type Syntax produces a value of type Sexp . Equivalent to (Sexpof Nothing ).

type

Datum

Applying datum->syntax to a value of type Datum produces a value of type Syntax . Equivalent to (Sexpof Syntax ).

1.5ControlπŸ”— i

The following type constructors and type respectively create and represent prompt tags and keys for continuation marks for use with delimited continuation functions and continuation mark functions.

type constructor

( Prompt-Tagof st)

Returns the type of a prompt tag to be used in a continuation prompt whose body produces the type s and whose handler has the type t. The type t must be a function type.

The domain of t determines the type of the values that can be aborted, using abort-current-continuation , to a prompt with this prompt tag.

Example:

- : (Prompt-Tagof Any Any)

#<continuation-prompt-tag:prompt-tag>

is the type of a prompt tag with unknown body and handler types and is the supertype of all prompt tag types. This type typically appears in programs via the combination of occurrence typing and continuation-prompt-tag? .

Example:
> (lambda: ([x: Any ])(if (continuation-prompt-tag? x)x(error "not a prompt tag!")))

- : (-> Any Prompt-TagTop)

#<procedure>

type constructor

( Continuation-Mark-Keyof t)

Returns the type of a continuation mark key that is used for continuation mark operations such as with-continuation-mark and continuation-mark-set->list . The type t represents the type of the data that is stored in the continuation mark with this key.

Example:

- : (Continuation-Mark-Keyof Any)

#<continuation-mark-key>

Is the type of a continuation mark key with unknown element type and is the supertype of all continuation mark key types. This type typically appears in programs via the combination of occurrence typing and continuation-mark-key? .

Example:
> (lambda: ([x: Any ])(if (continuation-mark-key? x)x(error "not a mark key!")))

- : (-> Any Continuation-Mark-KeyTop)

#<procedure>

1.6Other Type ConstructorsπŸ”— i

type constructor

( -> dom...rngopt-proposition)

(-> dom...rest* rng)
(-> dom...restoooboundrng)
(dom...-> rngopt-proposition)
(dom...rest* -> rng)
(dom...restooobound-> rng)
ooo = ...
dom = type
| mandatory-kw
| opt-kw
rng = type
| (Some(a...)type:#:+proposition)
| (Valuestype...)
mandatory-kw = keywordtype
opt-kw = [keywordtype]
opt-proposition =
| :type
|
:pos-proposition
neg-proposition
object
pos-proposition =
| #:+proposition...
neg-proposition =
| #:-proposition...
object =
| #:objectindex
proposition = Top
| Bot
| type
| (! type)
| (type@path-elem...index)
| (! type@path-elem...index)
| (and proposition...)
| (or proposition...)
| (implies proposition...)
path-elem = car
| cdr
index = positive-integer
| (positive-integerpositive-integer)
| identifier
The type of functions from the (possibly-empty) sequence dom.... to the rng type.

Examples:
> (λ ([x:Number ])x)

- : (-> Number Number)

#<procedure>

> (λ ()'hello)

- : (-> 'hello)

#<procedure>

The second form specifies a uniform rest argument of type rest, and the third form specifies a non-uniform rest argument of type rest with bound bound. The bound refers to the type variable that is in scope within the rest argument type.

Examples:
> (λ ([x:Number ]y:String * )(length y))

- : (-> Number String * Index)

#<procedure>

> ormap

- : (All (a c b ...)

(-> (-> a b ... b c) (Listof a) (Listof b) ... b (U False c)))

#<procedure:ormap>

In the third form, the ... introduced by ooo is literal, and bound must be an identifier denoting a type variable.

The doms can include both mandatory and optional keyword arguments. Mandatory keyword arguments are a pair of keyword and type, while optional arguments are surrounded by a pair of parentheses.

Examples:

(-> Path-String [#:mode (U 'binary 'text)] String)

> (:is-zero?:(-> Number #:equality(-> Number Number Any )[#:zeroNumber ]Any ))
> (define (is-zero?n#:equalityequality#:zero[zero0])
(equalitynzero))
> (is-zero?2#:equality= )

- : Any

#f

> (is-zero?2#:equalityeq? #:zero2.0)

- : Any

#f

When opt-proposition is provided, it specifies the proposition for the function type (for an introduction to propositions in Typed Racket, see Propositions and Predicates). For almost all use cases, only the simplest form of propositions, with a single type after a :, are necessary:

Example:

- : (-> Any Boolean : String)

#<procedure:string?>

The proposition specifies that when (string? x) evaluates to a true value for a conditional branch, the variable x in that branch can be assumed to have type String . Likewise, if the expression evaluates to #f in a branch, the variable does not have type String .

In some cases, asymmetric type information is useful in the propositions. For example, the filter function’s first argument is specified with only a positive proposition:

Example:
> filter

- : (All (a b)

(case->

(-> (-> a Any : #:+ b) (Listof a) (Listof b))

(-> (-> a Any) (Listof a) (Listof a))))

#<procedure:filter>

The use of #:+ indicates that when the function applied to a variable evaluates to a true value, the given type can be assumed for the variable. However, the type-checker gains no information in branches in which the result is #f.

Conversely, #:- specifies that a function provides information for the false branch of a conditional.

The other proposition cases are rarely needed, but the grammar documents them for completeness. They correspond to logical operations on the propositions.

The type of functions can also be specified with an infix -> which comes immediately before the rng type. The fourth through sixth forms match the first three cases, but with the infix style of arrow.

Examples:
> (:add2(Number -> Number ))
> (define (add2n)(+ n2))

Currently, because explicit packing operations for existential types are not supported, existential type results are only used to annotate accessors for Struct-Property

(Some(a... )type:#:+proposition) for rng specifies an existential type result, where the type variables a... may appear in type and opt-proposition. Unpacking the existential type result is done automatically while checking application of the function.

Changed in version 1.12 of package typed-racket-lib: Added existential type results

type constructor

( ->* (mandatory-dom...)optional-domsrestrng)

mandatory-dom = type
| keywordtype
optional-doms =
| (optional-dom...)
optional-dom = type
| keywordtype
rest =
| #:resttype
| #:rest-star(type...)
Constructs the type of functions with optional or rest arguments. The first list of mandatory-doms correspond to mandatory argument types. The list optional-doms, if provided, specifies the optional argument types.

Examples:
> (: append-bar(->* (String )(Positive-Integer )String ))
> (define (append-barstr[how-many1])
(apply string-append str(make-list how-many"bar")))

If provided, the #:resttype specifies the type of elements in the rest argument list.

Examples:
> (: +all(->* (Integer )#:restInteger (Listof Integer )))
> (define (+allinc. rst)
(map (λ ([x: Integer ])(+ xinc))rst))
> (+all20123)

- : (Listof Integer)

'(21 22 23)

A #:rest-star(type... ) specifies the rest list is a sequence of types which occurs 0 or more times (i.e. the Kleene closure of the sequence).

Examples:
> (: print-name+ages(->* ()#:rest-star(String Natural )Void ))
> (define (print-name+ages. names+ages)
(let loop([names+ages: (Rec x(U Null (List* String Natural x)))names+ages])
(when (pair? names+ages)
(printf "~a is ~a years old!\n"
(first names+ages)
(second names+ages))
(loop(cddr names+ages))))
(printf "done printing ~a ages"(/ (length names+ages)2)))
> (print-name+ages)

done printing 0 ages

> (print-name+ages"Charlotte"8"Harrison"5"Sydney"3)

Charlotte is 8 years old!

Harrison is 5 years old!

Sydney is 3 years old!

done printing 3 ages

Both the mandatory and optional argument lists may contain keywords paired with types.

Examples:
> (: kw-f(->* (#:xInteger )(#:yInteger )Integer ))
> (define (kw-f#:xx#:y[y0])(+ xy))

The syntax for this type constructor matches the syntax of the ->* contract combinator, but with types instead of contracts.

type

Top

type

Bot

These are propositions that can be used with -> . Top is the propositions with no information. Bot is the propositions which means the result cannot happen.

type

Procedure

is the supertype of all function types. The Procedure type corresponds to values that satisfy the procedure? predicate. Because this type encodes only the fact that the value is a procedure, and not its argument types or even arity, the type-checker cannot allow values of this type to be applied.

For the types of functions with known arity and argument types, see the -> type constructor.

Examples:
> (: my-listProcedure )
> (define my-listlist )
> (my-list"zwiebelkuchen""socca")

eval:91:0: Type Checker: cannot apply a function with

unknown arity;

function `my-list' has type Procedure which cannot be

applied

in: "socca"

type constructor

( U t...)

is the union of the types t... .

Example:
> (λ ([x: Real ])(if (> 0x)"yes"'no))

- : (-> Real (U 'no String))

#<procedure>

type constructor

( t...)

is the intersection of the types t... .

Example:
> ((λ #:forall(A)([x: ( Symbol A)])x)'foo)

- : 'foo

'foo

type constructor

( case-> fun-ty...)

is a function that behaves like all of the fun-tys, considered in order from first to last. The fun-tys must all be non-dependent function types (i.e. no preconditions or dependencies between arguments are currently allowed).

Example:

For the definition of add-map look into case-lambda: .

type

(tt1t2...)

is the instantiation of the parametric type t at types t1t2...

type

( All (a...)t)

(All (a...aooo)t)
is a parameterization of type t, with type variables a... . If t is a function type constructed with infix -> , the outer pair of parentheses around the function type may be omitted.

Examples:
> (: list-length: (All (A)(Listof A)-> Natural ))
> (define (list-lengthlst)
(if (null? lst)
0
(add1 (list-length(cdr lst)))))
> (list-length(list 123))

- : Integer [more precisely: Nonnegative-Integer]

3

type

( Some (a...)t)

Added in version 1.10 of package typed-racket-lib.

type constructor

( Values t...)

Returns the type of a sequence of multiple values, with types t... . This can only appear as the return type of a function.

Example:
> (values 123)

- : (values Integer Integer Integer) [more precisely: (Values One Positive-Byte Positive-Byte)]

1

2

3

Note that a type variable cannot be instantiated with a (Values ....) type. For example, the type (All (A)(-> A)) describes a thunk that returns exactly one value.

type

v

where v is a number, boolean or string, is the singleton type containing only that value

type

(quoteval)

where val is a Racket value, is the singleton type containing only that value

type

i

where i is an identifier can be a reference to a type name or a type variable

type

( Rec nt)

is a recursive type where n is bound to the recursive type in the body t

Examples:
> (define-type IntList(Rec List (Pair Integer (U List Null ))))

type

( Struct st)

is a type which is a supertype of all instances of the potentially-polymorphic structure type st. Note that structure accessors for st will not accept (Struct st) as an argument.

type

( Struct-Type st)

is a type for the structure type descriptor value for the structure type st. Values of this type are used with reflective operations such as struct-type-info .

Examples:

- : (StructType arity-at-least)

#<struct-type:arity-at-least>

- : (values

Symbol

Integer

Integer

(-> arity-at-least Nonnegative-Integer Any)

(-> arity-at-least Nonnegative-Integer Nothing Void)

(Listof Nonnegative-Integer)

(U False Struct-TypeTop)

Boolean)

[more precisely: (values

Symbol

Nonnegative-Integer

Nonnegative-Integer

(-> arity-at-least Nonnegative-Integer Any)

(-> arity-at-least Nonnegative-Integer Nothing Void)

(Listof Nonnegative-Integer)

(U False Struct-TypeTop)

Boolean)]

'arity-at-least

1

0

#<procedure:arity-at-least-ref>

#<procedure:arity-at-least-set!>

'(0)

#f

#f

is the supertype of all types for structure type descriptor values. The corresponding structure type is unknown for values of this top type.

Example:

- : (values (U False Struct-TypeTop) Boolean)

#<struct-type:arity-at-least>

#f

type constructor

( Prefab keytype...)

Describes a prefab structure with the given (implicitly quoted) prefab key key and specified field types.

Prefabs are more-or-less tagged polymorphic tuples which can be directly serialized and whose fields can be accessed by anyone. Subtyping is covariant for immutable fields and invariant for mutable fields.

When a prefab struct is defined with struct the struct name is bound at the type-level to the Prefab type with the corresponding key and field types and the constructor expects types corresponding to those declared for each field. The defined predicate, however, only tests whether a value is a prefab structure with the same key and number of fields, but does not inspect the fields’ values.

Examples:
> (struct person([name: String ])#:prefab)
> person

- : (-> String person)

#<procedure:person>

> person?

- : (-> Any Boolean : (Prefab person Any))

#<procedure:person?>

> person-name

- : (All (x) (case-> (-> (Prefab person x) x) (-> (Prefab person Any) Any)))

#<procedure:person-name>

> (person"Jim")

- : (Prefab person String)

'#s(person "Jim")

> (ann '#s(person"Dwight")person)

- : (Prefab person String)

'#s(person "Dwight")

> (ann '#s(person"Pam")(Prefab personString ))

- : person

'#s(person "Pam")

> (ann '#s(person"Michael")(Prefab personAny ))

- : (Prefab person Any)

'#s(person "Michael")

> (person'Toby)

eval:112:0: Type Checker: type mismatch

expected: String

given: 'Toby

in: Toby

> (ann #s(personToby)(Prefab personString ))

eval:113:0: Type Checker: type mismatch

expected: person

given: (Prefab person 'Toby)

in: String

> (ann '#s(personToby)(Prefab personSymbol ))

- : (Prefab person Symbol)

'#s(person Toby)

> (person?'#s(person"Michael"))

- : True

#t

> (person?'#s(personToby))

- : True

#t

> (struct employeeperson([schrute-bucks: Natural ])#:prefab)
> (employee"Oscar"10000)

- : (Prefab (employee person 1) String Nonnegative-Integer)

'#s((employee person 1) "Oscar" 10000)

> (ann '#s((employeeperson1)"Oscar"10000)employee)

- : (Prefab (employee person 1) String Nonnegative-Integer)

'#s((employee person 1) "Oscar" 10000)

> (ann '#s((employeeperson1)"Oscar"10000)
(Prefab (employeeperson1)String Natural ))

- : employee

'#s((employee person 1) "Oscar" 10000)

> (person?'#s((employeeperson1)"Oscar"10000))

- : True

#t

> (employee?'#s((employeeperson1)"Oscar"10000))

- : True

#t

> (employee'Toby-1)

eval:123:0: Type Checker: type mismatch

expected: String

given: 'Toby

in: -1

> (ann '#s((employeeperson1)Toby-1)
(Prefab (employeeperson1)Symbol Integer ))

- : (Prefab (employee person 1) Symbol Integer)

'#s((employee person 1) Toby -1)

> (person?'#s((employeeperson1)Toby-1))

- : True

#t

> (employee?'#s((employeeperson1)Toby-1))

- : True

#t

type

( PrefabTop keyfield-count)

Describes all prefab types with the (implicitly quoted) prefab-key key and field-count many fields.

For immutable prefabs this is equivalent to (Prefab keyAny ... ) with field-count many occurrences of Any . For mutable prefabs, this describes a prefab that can be read from but not written to (since we do not know at what type other code may have the fields typed at).

Examples:
> (struct point([x: Number ][y: Number ])
#:prefab
#:mutable)
> point

- : (-> Number Number point)

#<procedure:point>

> point-x

- : (All (a b)

(case->

(-> (Prefab (point #(0 1)) a b) a)

(-> (PrefabTop (point #(0 1)) 2) Any)))

#<procedure:point-x>

> point-y

- : (All (a b)

(case->

(-> (Prefab (point #(0 1)) a b) b)

(-> (PrefabTop (point #(0 1)) 2) Any)))

#<procedure:point-y>

> point?

- : (-> Any Boolean : (PrefabTop (point #(0 1)) 2))

#<procedure:point?>

> (define (maybe-read-xp)
(if (point?p)
(ann (point-xp)Any )
'not-a-point))
> (define (read-some-x-nump)
(if (point?p)
(ann (point-xp)Number )
-1))

eval:133:0: Type Checker: Polymorphic function `point-x'

could not be applied to arguments:

Types: (PrefabTop (point #(0 1)) 2)-> Any

Arguments: (PrefabTop (point #(0 1)) 2)

Expected result: Number

in: -1

Added in version 1.7 of package typed-racket-lib.

type constructor

( Struct-Property ty)

Describes a property that can be attached to a structure type. The property value must match the type ty.

Example:

(Struct-Property (U Exact-Nonnegative-Integer Input-Port))

Added in version 1.10 of package typed-racket-lib.

type

Self

This type can only appear in a Struct-Property type. A struct property value is attached to an instance of a structure type; the Self type refers to this instance.

Example:

(Struct-Property (-> Self Output-Port (U Boolean One Zero) AnyValues))

Added in version 1.10 of package typed-racket-lib.

type

Imp

This type can only appear in a Struct-Property type. An Imp value may be a structure subtype of the Self value, or another instance created by the same struct constructor.

Example:

(Struct-Property

(List

(-> Self Imp (-> Any Any Boolean) Any)

(-> Self (-> Any Integer) Integer)

(-> Self (-> Any Integer) Integer)))

Added in version 1.10 of package typed-racket-lib.

type

( Has-Struct-Property prop)

This type describes an instance of a structure type associcated with a Struct-Property named prop.

type constructor

An alias for U .

type constructor

Union

An alias for U .

type constructor

Intersection

An alias for .

type constructor

An alias for -> .

type constructor

→*

An alias for ->* .

type constructor

case→

An alias for case-> .

type

An alias for All .

1.7Other TypesπŸ”— i

type constructor

( Option t)

Either t or #f

type constructor

( Opaque t)

A type constructed using the #:opaque clause of require/typed .

top
up

AltStyle γ«γ‚ˆγ£γ¦ε€‰ζ›γ•γ‚ŒγŸγƒšγƒΌγ‚Έ (->γ‚ͺγƒͺγ‚ΈγƒŠγƒ«) /