Type expander library
1 #lang and module languages based on type-expander
1.1 #lang combining type-expander and typed/  racket
1.2 Module language combining type-expander and typed/  racket
1.3 #lang and module language combining type-expander and typed/  racket/  base
2 Defining new type expanders
define-type-expander
2.1 Attaching type expanders to existing identifiers
patch-type-expander
3 Using a type expander
4 Debugging type expanders
debug-type-expander
5 Compile-time aspects of type expanders
expand-type
apply-type-expander
prop:  type-expander
prop:  type-expander?
prop:  type-expander-ref
5.1 Syntax class for :
colon
5.2 Syntax classes for types
type
stx-type/  c
type-expand!
6 multi-id
7 Expansion model for type expanders
8 Built-in type expanders
8.1 Let
Let
8.2 Letrec
Letrec
8.3 Let*
Let*
8.4 Λ
Λ
8.5 Quasiquote
8.6 Currying type expanders
9 Common issues (FAQ)
10 Overloaded typed/  racket primitives
unsafe-cast
unsafe-cast/  no-expand
:
:  type
:  print-type
:  query-type/  args
:  query-type/  result
define-type
define
lambda
λ
case-lambda
case-lambda:
struct
define-struct/  exec
ann
cast
inst
let
let*
let-values
make-predicate
class
...*
11 Unimplemented typed/  racket primitives (will be overloaded in later versions).
pcase-lambda:
require/  opaque-type
require-typed-struct
require/  typed
require/  typed/  provide
require-typed-struct/  provide
define-predicate
define-type-alias
define-new-subtype
define-typed-struct
define-typed-struct/  exec
define-struct:
define-struct
struct:
λ:
lambda:
letrec
letrec-values
let/  cc
let/  ec
let:
let*:
letrec:
let-values:
letrec-values:
let/  cc:
let/  ec:
for
for/  list
for/  vector
for/  hash
for/  hasheq
for/  hasheqv
for/  and
for/  or
for/  sum
for/  product
for/  lists
for/  first
for/  last
for/  fold
for*
for*/  list
for*/  lists
for*/  vector
for*/  hash
for*/  hasheq
for*/  hasheqv
for*/  and
for*/  or
for*/  sum
for*/  product
for*/  first
for*/  last
for*/  fold
for/  set
for*/  set
do
do:
with-handlers
define-struct/  exec:
12 Deprecated export of colon via type-expander
colon
13 Using contract syntax to specify types
contract→type
:  contract→type
8.13.0.2

Type expander library🔗ℹ

Suzanne Soy <racket@suzanne.soy>

 (require type-expander) package: type-expander

This library is implemented using literate programming. The implementation details are presented in the Type expander: Implementation document.

It enhances typed/racket with type expanders, which are special macros that can appear wherever a regular type is usually expected, and must expand to a type. Type expanders are to types what match expanders are to match patterns.

It is based on Asumu Takikawa’s type expanders (see also his original pull request). Asumu Takikawa’s work attempted to integrate type expanders directly into Typed/Racket. This project instead implements type expanders as a library, which does not need any changes to the core Typed/Racket codebase. This shows the extensibility of Typed/Racket thanks to macros, and could serve as the basis for other projects which need to alter how Typed/Racket handles types.

The input for a type expander is the syntax used to call it, just as the input to a macro is the syntax used to call it. The output should be a type, which can itself contain type expanders.

This library works by shadowing the definitions of :, define, lambda etc. from typed/racket with versions which support type expanders.

1 #lang and module languages based on type-expander🔗ℹ

1.1 #lang combining type-expander and typed/racket🔗ℹ

The #lang type-expander language works like #lang typed/racket, but it initially imports the forms overridden by type-expander, instead of importing the original identifiers defined by typed/racket.
This language cannot be used as a module language, instead use type-expander/lang which provides the same bindings.

1.2 Module language combining type-expander and typed/racket🔗ℹ

This language is equivalent to #lang type-expander, but can also be used as a module language.

1.3 #lang and module language combining type-expander and typed/racket/base🔗ℹ

This language is similar to type-expander/lang, but it exports the identifiers from typed/racket/base instead of typed/racket.

2 Defining new type expanders🔗ℹ

syntax

(define-type-expander (name stx) . body)

(define-type-expander name transformer-function)
 
name = Identifier
     
stx = Identifier
     
transformer-function = (expr/c (-> syntax? syntax?))
The define-type-expander form binds name to a type expander, which can be used in places where a type would normally be expected.

For example, one could define the HomogeneousList type expander, which accepts a type t and an integer n, and produces a List type with n elements, each of type t:

(define-type-expander (HomogeneousList stx)
  (syntax-case stx ()
    [(_ t n)
     (number? (syntax-e #'n))
     (with-syntax ([(tᵢ ...) (stx-map (const #'t)
                                      (range (syntax-e #'n)))])
       #'(List tᵢ ...))]))

2.1 Attaching type expanders to existing identifiers🔗ℹ

syntax

(patch-type-expander name transformer-function)

 
name = Identifier
     
transformer-function = (expr/c (-> syntax? syntax?))
This macro records in a global table that name should behave according to the given transformer-function, when used as a type.

It allows attaching type expanders to existing identifiers, without shadowing them. It is used for example to attach the type expanders for quote, quasiquote, syntax and quasisyntax which are described below, and also for the curry type expander.

3 Using a type expander🔗ℹ

The HomogeneousList type expander defined above could be used in many of typed/racket’s forms.

(define-type three-ints (HomogeneousList 3 Integer))
(define (incr3 [x : three-ints]) : (HomogeneousList 3 Integer)
  (map add1 x))
(ann (incr3 '(1 2 3)) (HomogeneousList 3 Integer))

Type expanders can produce types which may contain other uses of type expanders, much in the same way as macros can expand to code calling other macros. The type expander can also produce directly a call to another type expander, just as a macro can expand to a call to another macro, without any extra surrounding syntax.

Contrarily to macros, if a call to a type expander is in the first position of more arguments, then the nested call is first expanded, and can produce the name of a second expander which will use the outer arguments, or can simply produce a polymorphic type which will be applied to the arguments. More than two levels of nesting are possible.

4 Debugging type expanders🔗ℹ

The first form enables printing of debugging information while expanding types, and the second form disables that behaviour. Debugging information is not printed by default.

Currently, when debugging information is enabled, the type expander prints at each step a human-readable representation of the syntax object it is about to expand, and once an expansion step finishes, it prints the original syntax object as well as its expanded form. The identifiers are adorned with superscripts indicating the scopes present on them. See the documentation for the debugging tool +scopes for more details.

5 Compile-time aspects of type expanders🔗ℹ

 (require type-expander/expander) package: type-expander

procedure

(expand-type stx)  PlainType

  stx : Type
Fully expands the type stx, which may contain any number of calls to type expanders. If those calls result in more type expanders, those are expanded too.

procedure

(apply-type-expander type-expander-stx stx)  Type

  type-expander-stx : Identifier
  stx : Syntax
Produces the result of applying the type expander bound to type-expander-stx to the syntax stx. Normally, the syntax stx would be of the form (type-expander-stx arg ) (similar to a macro call) or simply type-expander-stx (similar to an identifier macro). It is however possible to pass arbitrary syntax to the type expander, just as it is possible for macros (for example set! calls assignment transformer macros with the syntax (set! macro-name arg ) as an argument).

value

prop:type-expander : 
(struct-type-property/c
 (or/c exact-positive-integer?
       ( prop:type-expander? any/c any/c)
       ( any/c any/c)))

procedure

(prop:type-expander? v)  boolean?

  v : any/c

procedure

(prop:type-expander-ref v)  any/c

  v : prop:type-expander?
A structure type property to identify structure types that act as type expanders like the ones created by define-type-expander.

The property value must be a procedure of arity 1 or 2, or an exact-nonnegative-integer? designating a field index within the structure which contains such a procedure. If the procedure’s arity includes 2, then the first argument is the structure itself (which satisfies prop:type-expander?), and the second argument is the syntax object to transform. Otherwise, the single argument is the syntax object to transform.

The procedure serves as a syntax transformer when expanding the use of a type expander. If the type expander was in the first position of a syntax list (i.e. it looks like a macro or function call), then the whole syntax list is passed as an argument. Otherwise, just the identifier is passed as an argument, exactly as what would be done when calling an identifier macro. The procedure can support other use patterns if desired, so that it would be possible in principle to implement special type forms that behave in a way similar to set! Transformers.

5.1 Syntax class for :🔗ℹ

syntax-parse syntax class

colon

This library shadows the : identifier from typed/racket with a new definition :, adjusted to handle type expanders. Programs using the type-expander library will therefore use our version of :. The : identifier provided by this library is not free-identifier=? with the original : from typed/racket. This has an impact when writing patterns for the syntax/parse library, as the two identifiers : and : are not the same from the point of view of the ~literal pattern.

The colon syntax class is provided for-syntax by this library, and can be used in syntax-parse patterns, using c:colon for example. It matches both the original : and the new :, but not other : identifiers.

It can be used to write macros which expect either : identifier.

5.2 Syntax classes for types🔗ℹ

syntax-parse syntax class

type

Matches a type. For now, this is just an alias for expr, because types can contain arbitrary syntax thanks to type expanders.

value

stx-type/c : flat-contract?

Flat contract which recognises syntax objects representing types. For now, this is just an alias for syntax?, because types can contain arbitrary syntax thanks to type expanders.

Future versions may implement this as a non-flat contract, in order to be able to check that in a macro’s result, the syntax for a type is not used as an expression, and vice versa.

syntax-parse syntax class

type-expand!

Matches a type t, and provides an attribute named expanded which contains the result of (expand-type #'t). For now, type-expand does not perform any check other than verifying that t is an expr, because types can contain arbitrary syntax thanks to type expanders.

6 multi-id🔗ℹ

Type expanders are supported by the multi-id library. It is therefore easy to define an identifier which acts as a type expander and match expander as well as a regular racket macro and/or identifier macro. This can be useful to define feature-rich data structures, which need to provide all of the above features.

7 Expansion model for type expanders🔗ℹ

The expansion model for type expanders is similar to the expansion model for macros. There are a few differences, however, which are presented below.

8 Built-in type expanders🔗ℹ

There are several built-in expanders. Some are documented here, while others are listed in (part ("(lib type-expander/type-expander.hl.rkt)" "Cases_handled_by_expand-type")). Their API should be considered unstable, and may change in the future.

8.1 Let🔗ℹ

type expander

(Let ([Vᵢ Eᵢ] ...) τ)

 
Vᵢ = Identifier
     
Eᵢ = Type
     
τ = Type
The Let form binds each type expression Eᵢ (which may contain uses of type expanders bound outside of the Let form) to the identifier Vᵢ. The type τ can contain type expanders and can refer to occurrences of the bound Vᵢ identifiers, which will expand to Eᵢ. The Let form therefore behaves is a way similar to let-syntax.

Examples:
> (ann '(1 2 3)
       (Let ([Foo Number])
         (Listof Foo)))

- : (Listof Number)

'(1 2 3)

> (ann '(1 2 3)
       (Listof Foo))

eval:2:0: Type Checker: parse error in type;

 type name `Foo' is unbound

  in: Foo

Example:
> (ann '([1 . "a"] [2 . b] [3 . 2.71])
       (Let ([Foo (Λ (_ T)
                    #'(Pairof Number T))])
         (List (Foo String)
               (Foo Symbol)
               (Foo Float))))

- : (List (Pairof Number String) (Pairof Number Symbol) (Pairof Number Flonum))

'((1 . "a") (2 . b) (3 . 2.71))

Examples:
> (ann '(a b c)
       (Let ([Foo Number])
         (Let ([Foo String])
           (Let ([Foo Symbol])
             (Listof Foo)))))

- : (Listof Symbol)

'(a b c)

> (ann '(a b c)
       (Let ([Foo Number])
         (Listof (Let ([Foo String])
                   (Let ([Foo Symbol])
                     Foo)))))

- : (Listof Symbol)

'(a b c)

8.2 Letrec🔗ℹ

type expander

(Letrec ([Vᵢ Eᵢ] ...) τ)

Like Let, but all the Vᵢ identifiers are bound within all the Eᵢ type expressions. This means the type expression within an Eᵢ can refer to any Vᵢ of the same Letrec.

8.3 Let*🔗ℹ

type expander

(Let* ([Vᵢ Eᵢ] ...) τ)

Like Let, but all the preceding Vᵢ identifiers are bound each Eᵢ type expression. This means the type expression within an Eᵢ can refer to any Vᵢ already bound above it, but not to the Vᵢ it is being bound to, nor to the following Vᵢ.

8.4 Λ🔗ℹ

type expander

(Λ formals . body)

 
stx = Identifier
The Λ form (a capital λ) can be used to construct an anonymous type expander. It is equivalent to replacing the whole (Λ formals . body) form with generated-id, where generated-id is defined as a named type expander as follows:

(define-type-expander (gen-id gen-stx-id)
  (auto-syntax-case gen-stx-id ()
    [formals (let () . body)]))

where id and gen-stx-id are fresh unique identifiers.

Since Λ relies on auto-syntax-case, the syntax pattern variables bound by formals can also be used outside of syntax templates, in which case they evaluate to (syntax->datum #'pvar).

Examples:
(require (for-syntax racket/list racket/function))

 

> (ann '(1 2 3 4)
       ((Λ (_ T n)
          #`(List #,@(map (const #'T) (range n))))
        Number 4))

- : (List Number Number Number Number)

'(1 2 3 4)

8.5 Quasiquote🔗ℹ

The type expander library also adds support for quasiquoting in types: The type `(a (1 b) ,String) is expanded to (List 'a (List 1 'b) String).

Example:
> (ann '(a (1 b) "foo")
       `(a (1 b) ,String))

- : (List 'a (List One 'b) String)

'(a (1 b) "foo")

The quote, quasiquote, syntax and quasisyntax identifiers are interpreted specially within type expressions. The quote identifier can be used to describe a type matching containing only the quoted value. Similarly, syntax can be used to describe the type of the quoted syntax object, without the need to insert Syntaxof by hand around each part of the type. Note that the type #'(a b c) will match the syntax object #'(a b c), but not the syntax object #(a b . (c)), i.e. the generated type is sensitive to the distinction between syntax pairs and syntax lists. It is possible that a future version of this library provides another type expander which accepts both. The quasiquote and quasisyntax forms allow the use of unquote and unsyntax, respectively.

8.6 Currying type expanders🔗ℹ

The curry special type-expander form can be used to curry in some arguments to a type expander.

Example:
> (ann '([a . 1] [a . b] [a . "c"])
       (Let ([PA (curry Pairof 'a)])
         (List (PA 1) (PA 'b) (PA "c"))))

- : (List (Pairof 'a One) (Pairof 'a 'b) (Pairof 'a "c"))

'((a . 1) (a . b) (a . "c"))

9 Common issues (FAQ)🔗ℹ

10 Overloaded typed/racket primitives🔗ℹ

syntax

(unsafe-cast value type)

We define an unsafe-cast form which is not (yet) provided by Typed/Racket. It works like cast, but does not generate a predicate to check that the value is indeed of the given type. It can therefore be used to cast values to types for which cast would fail at compile-time when trying to generate the predicate, for example function types, or any type which translates to a chaperone contract.

syntax

(unsafe-cast/no-expand value type)

Like unsafe-cast, but does not expand the type. Can be useful for types which are not completely handled by type-expander, for example function types with filters.

syntax

(: ...)

Overloaded version of : from typed/racket.

syntax

(:type ...)

Overloaded version of :type from typed/racket.

syntax

(:print-type ...)

Overloaded version of :print-type from typed/racket.

syntax

(:query-type/args ...)

Overloaded version of :query-type/args from typed/racket.

syntax

(:query-type/result ...)

Overloaded version of :query-type/result from typed/racket.

syntax

(define-type ...)

Overloaded version of define-type from typed/racket.

syntax

(define ...)

Overloaded version of define from typed/racket.

syntax

(lambda ...)

Overloaded version of lambda from typed/racket.

syntax

(λ ...)

Overloaded version of λ from typed/racket.

syntax

(case-lambda ...)

Overloaded version of case-lambda from typed/racket.

syntax

(case-lambda: ...)

Overloaded version of case-lambda: from typed/racket.

syntax

(struct ...)

Overloaded version of struct from typed/racket.

syntax

(define-struct/exec ...)

Overloaded version of define-struct/exec from typed/racket.

syntax

(ann ...)

Overloaded version of ann from typed/racket.

syntax

(cast ...)

Overloaded version of cast from typed/racket.

syntax

(inst ...)

Overloaded version of inst from typed/racket.

syntax

(let ...)

Overloaded version of let from typed/racket.

syntax

(let* ...)

Overloaded version of let* from typed/racket.

syntax

(let-values ...)

Overloaded version of let-values from typed/racket.

syntax

(make-predicate ...)

Overloaded version of make-predicate from typed/racket.

syntax

(class ...)

Overloaded version of class from typed/racket.

syntax

...*

Overloaded version of ...*, which is interpreted specially by typed/racket. It seems to be equivalent to * for indicating the type of a rest argument within a typed λ form.

11 Unimplemented typed/racket primitives (will be overloaded in later versions).🔗ℹ

syntax

(pcase-lambda: ...)

Overloaded version of pcase-lambda: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(require/opaque-type ...)

Overloaded version of require/opaque-type from typed/racket (not implemented for the type-expander library yet, just throws an error).
Overloaded version of require-typed-struct from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(require/typed ...)

Overloaded version of require/typed from typed/racket (not implemented for the type-expander library yet, just throws an error).
Overloaded version of require/typed/provide from typed/racket (not implemented for the type-expander library yet, just throws an error).
Overloaded version of require-typed-struct/provide from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-predicate ...)

Overloaded version of define-predicate from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-type-alias ...)

Overloaded version of define-type-alias from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-new-subtype ...)

Overloaded version of define-new-subtype from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-typed-struct ...)

Overloaded version of define-typed-struct from typed/racket (not implemented for the type-expander library yet, just throws an error).
Overloaded version of define-typed-struct/exec from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-struct: ...)

Overloaded version of define-struct: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-struct ...)

Overloaded version of define-struct from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(struct: ...)

Overloaded version of struct: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(λ: ...)

Overloaded version of λ: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(lambda: ...)

Overloaded version of lambda: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(letrec ...)

Overloaded version of letrec from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(letrec-values ...)

Overloaded version of letrec-values from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let/cc ...)

Overloaded version of let/cc from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let/ec ...)

Overloaded version of let/ec from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let: ...)

Overloaded version of let: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let*: ...)

Overloaded version of let*: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(letrec: ...)

Overloaded version of letrec: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let-values: ...)

Overloaded version of let-values: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(letrec-values: ...)

Overloaded version of letrec-values: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let/cc: ...)

Overloaded version of let/cc: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(let/ec: ...)

Overloaded version of let/ec: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for ...)

Overloaded version of for from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/list ...)

Overloaded version of for/list from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/vector ...)

Overloaded version of for/vector from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/hash ...)

Overloaded version of for/hash from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/hasheq ...)

Overloaded version of for/hasheq from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/hasheqv ...)

Overloaded version of for/hasheqv from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/and ...)

Overloaded version of for/and from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/or ...)

Overloaded version of for/or from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/sum ...)

Overloaded version of for/sum from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/product ...)

Overloaded version of for/product from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/lists ...)

Overloaded version of for/lists from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/first ...)

Overloaded version of for/first from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/last ...)

Overloaded version of for/last from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/fold ...)

Overloaded version of for/fold from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for* ...)

Overloaded version of for* from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/list ...)

Overloaded version of for*/list from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/lists ...)

Overloaded version of for*/lists from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/vector ...)

Overloaded version of for*/vector from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/hash ...)

Overloaded version of for*/hash from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/hasheq ...)

Overloaded version of for*/hasheq from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/hasheqv ...)

Overloaded version of for*/hasheqv from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/and ...)

Overloaded version of for*/and from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/or ...)

Overloaded version of for*/or from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/sum ...)

Overloaded version of for*/sum from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/product ...)

Overloaded version of for*/product from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/first ...)

Overloaded version of for*/first from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/last ...)

Overloaded version of for*/last from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/fold ...)

Overloaded version of for*/fold from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for/set ...)

Overloaded version of for/set from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(for*/set ...)

Overloaded version of for*/set from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(do ...)

Overloaded version of do from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(do: ...)

Overloaded version of do: from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(with-handlers ...)

Overloaded version of with-handlers from typed/racket (not implemented for the type-expander library yet, just throws an error).

syntax

(define-struct/exec: ...)

Overloaded version of define-struct/exec: from typed/racket (not implemented for the type-expander library yet, just throws an error).

12 Deprecated export of colon via type-expander🔗ℹ

syntax

colon

NOTE: This reprovide is deprecated; use colon from type-expander/expander, instead. The colon identifier is re-exported for-syntax as colon by type-expander. Prefer instead explicitly using (require (for-syntax type-expander/expander)), as the re-export will be removed in future versions.

13 Using contract syntax to specify types🔗ℹ

 (require type-expander/contracts-to-types)
  package: type-expander

syntax

(contract→type contract)

(contract->type contract)
This is a simple type expander which translates common contracts to types. Note that it only supports a limited number of contract constructors. The following are supported: or/c, and/c (the translation may produce a type too complex for Typed/Racket to understand properly, though), listof, list/c, *list/c, vectorof, vector/c, cons/c, number?, integer?, string?, symbol?, char?, boolean?, bytes?, void?, null?, empty?, list?, exact-nonnegative-integer?, exact-positive-integer?, syntax/c, parameter/c, promise/c, suggest/c, flat-rec-contract, some uses of -> and ->*, 'quoted-datum, `quasiquoted-datum-with-unquoted-types. Literal data (numbers, strings, characters, booleans, byte strings, regular expressions and byte regular expressions) are also interpreted as singleton types.

Furthermore, using ,τ anywhere outside of a quoted datum will leave the type τ unchaged, allowing the user to manually convert to types only the parts which cannot be converted automatically.

syntax

(:contract→type contract)

(:contract->type contract)
Prints a representation of the contract translated as a type. It is then possible to copy-paste that result into the code.

Examples:
> (require type-expander/lang
           racket/contract/base
           type-expander/contracts-to-types)
> (:contract→type (list/c 1 2 "str" (or/c integer? string?)))

(List 1 2 "str" (U Integer String))