PLAI Typed Language
1 Definitions
define
define-values
define-type
define-type-alias
require
trace
module
module+
include
define-syntax-rule
define-syntax
splice
2 Expressions
has-type
true
false
quote
quasiquote
unquote
unquote-splicing
#%app
lambda
λ
if
cond
case
begin
when
unless
local
letrec
let
let*
shared
parameterize
set!
and
or
list
vector
values
type-case
try
empty
cons
first
rest
empty?
cons?
second
third
fourth
list-ref
length
append
reverse
member
map
map2
filter
foldl
foldr
build-list
not
+
-
*
/
modulo
remainder
=
>
<
>=
<=
min
max
floor
ceiling
add1
sub1
zero?
odd?
even?
symbol=?
string=?
string-append
to-string
string->symbol
symbol->string
string-ref
string-length
substring
char=?
string->list
list->string
s-exp-symbol?
s-exp->symbol
symbol->s-exp
s-exp-number?
s-exp->number
number->s-exp
s-exp-string?
s-exp->string
string->s-exp
s-exp-boolean?
s-exp->boolean
boolean->s-exp
s-exp-list?
s-exp->list
list->s-exp
identity
equal?
eq?
error
display
read
box
unbox
set-box!
make-vector
vector-ref
vector-set!
vector-length
pair
fst
snd
make-parameter
parameter-ref
parameter-set!
make-hash
hash
hash-ref
hash-set!
hash-remove!
hash-set
hash-remove
hash-keys
none
some
some-v
none?
some?
call/  cc
let/  cc
test
test/  exn
print-only-errors
time
3 Types
number
boolean
symbol
string
char
s-expression
void
->
listof
boxof
vectorof
parameterof
hashof
optionof
4 Syntactic Literals
typed-in
opaque-type-in
:
5 Type Checking and Inference
6 Untyped with Typed Syntax
typed-in
opaque-type-in
6.3.90.900

PLAI Typed Language

 #lang plai-typed package: plai-typed

The plai-typed language is a statically typed language that resembles the plai language, though with a smaller set of syntactic forms and built-in functions.

The body of a plai-typed module is a sequence of definitions and expressions. Like the plai languages the module exports all top-level definitions. When a plai-typed module is imported into a module that does not use plai-typed, the imports have contracts (matching reflecting the exported bindings’ types).

    1 Definitions

    2 Expressions

    3 Types

    4 Syntactic Literals

    5 Type Checking and Inference

    6 Untyped with Typed Syntax

1 Definitions

In a define-type declaration, the contract/predicate position for variant fields changes to a colon followed by a type. In addition, define and lambda forms support type annotations on arguments and for results. The syntax is otherwise merely restricted from the normal PLAI language.

syntax

(define id expr)

(define id : type expr)
(define (id id/type ...) expr)
(define (id id/type ...) : type expr)
 
id/type = id
  | [id : type]
The definition form with optional type annotations. A type written after (id id/type ...) declares the result type of a function.

syntax

(define-values (id/type ...) expr)

 
id/type = id
  | [id : type]
Matches a tuple produced (via values) by expr.

syntax

(define-type tyid/abs
  [variant-id (field-id : type)]
  ...)
 
tyid/abs = id
  | (id 'arg-id ...)
Defines a type (when tyid/abs is id) or type constructor (when tyid/abs has the form (id 'id ...)) with its variants.

syntax

(define-type-alias tyid/abs type)

 
tyid/abs = id
  | (id 'arg-id ...)
Defines a type alias id. Then tyid/abs is id, then using id is the same as using type. When tyid/abs is (id 'arg-id ...), then using (id arg-type ...) is the same as using type with each 'arg-id replaced by the corresponding arg-type.

syntax

(require spec ...)

 
spec = module-path
  | (typed-in module-path [id : type] ...)
  | (opaque-type-in module-path [type-id predicate-id] ...)
  | (rename-in spec [orig-id new-id] ...)
Imports from each module-path.

When a module-path is not wrapped with typed-in or opaque-type-in, then module-path must refer to a module that is implemented with plai-typed.

When module-path is wrapped with typed-in, then only the specified ids are imported from module-path, and the type system assumes (without static or additional dynamic checks) the given type for each id.

When module-path is wrapped with opaque-type-in, then the corresponding type-ids are bound as opaque datatypes, where predicate-id from module-path is a run-time predicate (used for contracts as needed for cooperation with untyped code) for instances of the datatype.

syntax

(trace id ...)

Traces subsequent calls—showing arguments and results—for functions bound to the ids. This form can be used only in a module top level, and only for tracing functions defined within the module.

syntax

(module id module-path form ...)

Declares a submodule named id, which can be required in the enclosing module using 'id or (submod "." id):

(module sub plai-typed
  (define n 8))
(require 'sub)
(+ n 1)

syntax

(module+ id form ...)

Declares/extends a submodule named id, which is particularly useful for defining a test submodule to hold tests that precede relevant definitions (since the submodule implicitly imports the bindings of its enclosing module, and DrRacket or raco test runs the test submodule):

(module+ test
  (test 11 (add-one 10)))
 
(define (add-one n)
  (+ 1 n))

syntax

(include path-spec)

Copy the content of path-spec in place of the include form, which can only be used in a top-level position.

syntax

(define-syntax-rule (id pattern ...) template)

syntax

(define-syntax id macro-expr)

(define-syntax (id arg-id) macro-body ...)
 
macro = (syntax-rules ....)
  | (lambda ....)
Defines a macro. In a macro-expr or macro-body, the bindings of racket/base are available.

A macro of the form

(define-syntax-rule (id pattern ...) template)

is equivalent to

(define-syntax id
  (syntax-rules ()
   [(id pattern ...) template]))

syntax

(splice form ...)

Equivalent to the forms sequence in a module or top-level context, which is useful for producing multiple definitions from a macro.

2 Expressions

An expression can be a literal constant that is a number (type number), a string (type string), a symbol (type symbol) written with quote or ', an S-expression (type s-expression) also written with quote or ', #t (type boolean), #f (type boolean), or a character (type char). An expression also can be a bound identifier (in which case its type comes from its binding).

syntax

(has-type expr : type)

Equivalent to expr, but declares/asserts that expr has type type.

value

true : boolean

value

false : boolean

syntax

(quote s-exp)

 
s-exp = id
  | number
  | string
  | boolean
  | (s-exp ...)
A symbol (when the s-exp is an identifier) or a literal S-expression.

syntax

(quasiquote qq-form)

 
qq-form = id
  | number
  | string
  | boolean
  | (qq-form ...)
  | (unquote expr)
  | (unquote-splicing expr)
  | (quasiquote expr)

syntax

unquote

syntax

unquote-splicing

An S-expression with escapes. An id (to generate a symbol S-expression) in a qq-form must not be unquote, unquote-splicing, or quasiquote.

syntax

(#%app expr expr ...)

A function call, which is normally written without the #%app keyword.

syntax

(lambda (id/ty ...) expr)

(lambda (id/ty ...) : type expr)
 
id/ty = id
  | [id : type]
A procedure. When a type is written after (id/ty ...), it declares he result type of the function.

syntax

λ

An alias for lambda.

syntax

(if test-expr expr expr)

syntax

(cond [test-expr expr] ...)

(cond [test-expr expr] ... [else expr])
Conditionals. Each test-expr must have type boolean.

syntax

(case expr [(id-or-number ...) expr] ...)

(case expr [(id-or-number ...) expr] ... [else expr])
Case dispatch on symbols or numbers.

The dispatching mode, symbol or number, is inferred from the id-or-numbers, which must all be symbols or numbers for a given use of case. If no clause provides a number or symbol, then symbol dispatch is inferred.

syntax

(begin expr ...+)

Sequence.

syntax

(when test-expr expr ...+)

syntax

(unless test-expr expr ...+)

Conditional sequence.

syntax

(local [definition ...] expr)

syntax

(letrec ([id expr] ...) expr)

syntax

(let ([id expr] ...) expr)

syntax

(let* ([id expr] ...) expr)

Local binding.

syntax

(shared ([id expr] ...) expr)

Cyclic- and shared-structure binding.

syntax

(parameterize ([param-expr val-expr] ...) expr)

Dynamic binding. Each param-expr must have type (parameterof type) where the corresponding val-expr has type type.

syntax

(set! id expr)

Assignment.

syntax

(and expr ...)

syntax

(or expr ...)

Boolean combination. The exprs must have type boolean.

syntax

(list elem ...)

Builds a list. All elems must have the same type.

syntax

(vector elem ...)

Builds a vector. All elems must have the same type.

syntax

(values elem ...)

Combines multiple values into tuple, where a tuple containing one value is equivalent to the value. Match a tuple result using define-values.

The type of each elem is independent.

syntax

(type-case tyid/abs val-expr
  [variant-id (field-id ...) expr] ...)
(type-case tyid/abs val-expr
  [variant-id (field-id ...) expr] ...
  [else expr])
 
tyid/abs = id
  | (id type ...)
Variant dispatch, where val-expr must have type tyid/abs.

syntax

(try expr (lambda () handle-expr))

Either returns expr’s result or catches an exception raised by expr and calls handle-expr.

value

empty : (listof 'a)

value

cons : ('a (listof 'a) -> (listof 'a))

value

first : ((listof 'a) -> 'a)

value

rest : ((listof 'a) -> (listof 'a))

value

empty? : ((listof 'a) -> boolean)

value

cons? : ((listof 'a) -> boolean)

value

second : ((listof 'a) -> 'a)

value

third : ((listof 'a) -> 'a)

value

fourth : ((listof 'a) -> 'a)

value

list-ref : ((listof 'a) number -> 'a)

value

length : ((listof 'a) -> number)

value

append : ((listof 'a) (listof 'a) -> (listof 'a))

value

reverse : ((listof 'a) -> (listof 'a))

value

member : ('a (listof 'a) -> boolean)

value

map : (('a -> 'b) (listof 'a) -> (listof 'b))

value

map2 : (('a 'b -> 'c) (listof 'a) (listof 'b) -> (listof 'c))

value

filter : (('a -> boolean) (listof 'a) -> (listof 'a))

value

foldl : (('a 'b -> 'b) 'b (listof 'a) -> 'b)

value

foldr : (('a 'b -> 'b) 'b (listof 'a) -> 'b)

value

build-list : (number (number -> 'a) -> (listof 'a))

List primitives.

value

not : (boolean -> boolean)

Boolean primitive.

value

+ : (number number -> number)

value

- : (number number -> number)

value

* : (number number -> number)

value

/ : (number number -> number)

value

modulo : (number number -> number)

value

remainder : (number number -> number)

value

= : (number number -> boolean)

value

> : (number number -> boolean)

value

< : (number number -> boolean)

value

>= : (number number -> boolean)

value

<= : (number number -> boolean)

value

min : (number number -> number)

value

max : (number number -> number)

value

floor : (number -> number)

value

ceiling : (number -> number)

value

add1 : (number -> number)

value

sub1 : (number -> number)

value

zero? : (number -> boolean)

value

odd? : (number -> boolean)

value

even? : (number -> boolean)

Numeric primitives.

Symbol primitive.

String primitives.

value

char=? : (char char -> boolean)

value

string->list : (string -> (listof char))

value

list->string : ((listof char) -> string)

Character primitives.

Coercion primitives to and from S-expressions.

The s-exp-symbol? function determines whether an S-expression is a symbol; in that case, s-exp->symbol acts the identity function to produce the symbol, otherwise an exception is raised. The symbol->s-exp function similarly acts as the identity function to view a symbol as an S-expression.

The other functions work similarly for numbers, strings, booleans, and lists of S-expressions.

value

identity : ('a -> 'a)

Identity primitive.

value

equal? : ('a 'a -> boolean)

value

eq? : ('a 'a -> boolean)

Comparison primitives.

value

error : (symbol string -> 'a)

Error primitive.

value

display : ('a -> void)

Output primitive.

value

read : (-> s-expression)

Input primitive.

value

box : ('a -> (boxof 'a))

value

unbox : ((boxof 'a) -> 'a)

value

set-box! : ((boxof 'a) 'a -> void)

Box primitives.

value

make-vector : (number 'a -> (vectorof 'a))

value

vector-ref : ((vectorof 'a) number -> 'a)

value

vector-set! : ((vectorof 'a) number 'a -> void)

value

vector-length : ((vectorof 'a) -> number)

Vector primitives.

value

pair : ('a 'b -> ('a * 'b))

value

fst : (('a * 'b) -> 'a)

value

snd : (('a * 'b) -> 'b)

Constructor and selectors for tuples containing two values.

value

make-parameter : ('a -> (parameterof 'a))

value

parameter-ref : ((parameterof 'a) -> 'a)

value

parameter-set! : ((parameterof 'a) 'a -> void)

Parameter primitives.

value

make-hash : ((listof ('a * 'b)) -> (hashof 'a 'b))

value

hash : ((listof ('a * 'b)) -> (hashof 'a 'b))

value

hash-ref : ((hashof 'a 'b) 'a -> (optionof 'b))

value

hash-set! : ((hashof 'a 'b) 'a 'b -> void)

value

hash-remove! : ((hashof 'a 'b) 'a -> void)

value

hash-set : ((hashof 'a 'b) 'a 'b -> (hashof 'a 'b))

value

hash-remove : ((hashof 'a 'b) 'a -> (hashof 'a 'b))

value

hash-keys : ((hashof 'a 'b) -> (listof 'a))

Hash table primitives. The make-hash function creates a mutable hash table for use with hash-set! and hash-remove!, while the hash function creates an immutable hash table for use with hash-set and hash-remove. The hash-ref and hash-keys functions work on both mutable and immutable hash tables.

value

none : (-> (optionof 'a))

value

some : ('a -> (optionof 'a))

value

some-v : ((optionof 'a) -> 'a)

value

none? : ((optionof 'a) -> bool)

value

some? : ((optionof 'a) -> bool)

Option constructors, selector, and predicates. See optionof.

value

call/cc : ((('a -> 'b) -> 'a) -> 'a)

syntax

(let/cc id expr)

Continuation primitive, where (let/cc id expr) is equivalent to (call/cc (lambda (id) expr)).

syntax

(test expr expr)

syntax

(test/exn expr string-expr)

value

print-only-errors : (boolean -> void)

Test primitive forms. The test and test/exn forms have type void, although they do not actually produce a void value; instead, they produce results suitable for automatic display through a top-level expression, and the void type merely prevents your program from using the result.

See also module+.

syntax

(time expr)

Shows the time taken to evaluate expr.

3 Types

syntax

number

syntax

boolean

syntax

symbol

syntax

string

syntax

char

syntax

s-expression

syntax

void

Primitive types.

The void identifier also works as an expression of type (-> void).

syntax

(type ... -> type)

Types for functions.

syntax

(type * ...+)

Types for tuples.

syntax

()

Type for the empty tuple.

syntax

(listof type)

Types for lists of elements.

syntax

(boxof type)

Types for mutable boxes.

syntax

(vectorof type)

Types for vectors of elements.

syntax

(parameterof type)

Types for parameters.

syntax

(hashof type type)

Types for hash tables.

syntax

(optionof type)

Defined as
(define-type (optionof 'a)
  [none]
  [some (v : 'a)])
and used, for example, for the result of hash-ref.

4 Syntactic Literals

syntax

typed-in

syntax

opaque-type-in

syntax

:

Syntactic literals for use in declarations such as define and require; see define and require for more information.

5 Type Checking and Inference

Type checking and inference is just as in ML (Hindley-Milner), with a few small exceptions:

When typechecking fails, the error messages reports and highlights (in pink) all of the expressions whose type contributed to the failure. That’s often too much information. As usual, explicit type annotations can help focus the error message.

6 Untyped with Typed Syntax

 #lang plai-typed/untyped package: plai-typed
The plai-typed/untyped language supports the same syntax as plai-typed, but it performs no type checking.

The define-syntax, define-syntax-rule, module+, and require forms from plai-typed/untyped are the bindings from racket/base instead of plai-typed.

Forms for require that simulate the ones from plai-typed by expanding to uses of only-in.