Chapter 11. Syntactic Extension and Modules

This chapter describes the Chez Scheme extensions to the syntax-case syntactic abstraction mechanism now standardized in the Revised6 Report. These extensions include the module system (Section 11.5), meta definitions (Section 11.8), conditional expansion (Section 11.9) syntax-rules fenders, fluid-let-syntax, and include.

Section 11.1. Fluid Keyword Bindings

Keyword bindings established via the Revised6 Report define-syntax, let-syntax, or letrec-syntax forms may be rebound temporarily with fluid-let-syntax.

syntax: (fluid-let-syntax ((keyword expr) ...) form1 form2 ...)
returns: see explanation
libraries: (chezscheme)

Each expr must evaluate to a transformer. fluid-let-syntax is similar to the standard let-syntax, except that instead of introducing new bindings for the keywords keyword ..., fluid-let-syntax temporarily alters the existing bindings for the keywords during the expansion of its body. That is, during the expansion of form1 form2 ..., the visible lexical (or top-level) binding for each keyword is temporarily replaced by a new association between the keyword and the corresponding transformer. This affects any references to the keyword that resolve to the same lexical (or top-level) binding whether the references occur in the text of the body or are introduced during its expansion. In contrast, let-syntax captures only those references that occur within the text of its body.

The following example shows how fluid-let-syntax differs from let-syntax.

(let ([f (lambda (x) (+ x 1))])
  (let-syntax ([g (syntax-rules ()
                    [(_ x) (f x)])])
    (let-syntax ([f (syntax-rules ()
                      [(_ x) x])])
      (g 1)))) <graphic> 2

(let ([f (lambda (x) (+ x 1))])
  (let-syntax ([g (syntax-rules ()
                    [(_ x) (f x)])])
    (fluid-let-syntax ([f (syntax-rules ()
                            [(_ x) x])])
      (g 1)))) <graphic> 1

The two expressions are identical except that the inner let-syntax form in the first expression is a fluid-let-syntax form in the second. In the first expression, the f occurring in the expansion of (g 1) refers to the let-bound variable f, whereas in the second it refers to the keyword f by virtue of the fluid syntax binding for f.

The following code employs fluid-let-syntax in the definition of a define-integrable form that is similar to define for procedure definitions except that it causes the code for the procedure to be integrated, or inserted, wherever a direct call to the procedure is found. No semantic difference is visible between procedures defined with define-integrable and those defined with define, except that a top-level define-integrable form must appear before the first reference to the defined identifier. Lexical scoping is preserved, the actual parameters in an integrated call are evaluated once and at the proper time, integrable procedures may be used as first-class values, and recursive procedures do not cause indefinite recursive expansion.

(define-syntax define-integrable
  (syntax-rules (lambda)
    [(_ name (lambda formals form1 form2 ...))
     (begin
       (define xname
         (fluid-let-syntax ([name (identifier-syntax xname)])
           (lambda formals form1 form2 ...)))
       (define-syntax name
         (lambda (x)
           (syntax-case x ()
             [_ (identifier? x) #'xname]
             [(_ arg (... ...))
              #'((fluid-let-syntax ([name (identifier-syntax xname)])
                   (lambda formals form1 form2 ...))
                  arg
                  (... ...))]))))]))

A define-integrable has the following form.

(define-integrable name lambda-expression)

A define-integrable form expands into a pair of definitions: a syntax definition of name and a variable definition of xname. The transformer for name converts apparent calls to name into direct calls to lambda-expression. Since the resulting forms are merely direct lambda applications (the equivalent of let expressions), the actual parameters are evaluated exactly once and before evaluation of the procedure's body, as required. All other references to name are replaced with references to xname. The definition of xname binds it to the value of lambda-expression. This allows the procedure to be used as a first-class value. Because xname is introduced by the transformer, the binding for xname is not visible anywhere except where references to it are introduced by the the transformer for name.

Within lambda-expression, wherever it appears, name is rebound to a transformer that expands all references into references to xname. The use of fluid-let-syntax for this purpose prevents indefinite expansion from indirect recursion among integrable procedures. This allows the procedure to be recursive without causing indefinite expansion. Nothing special is done by define-integrable to maintain lexical scoping, since lexical scoping is maintained automatically by the expander.

Chez Scheme integrate locally defined procedures automatically when it is appropriate to do so. It cannot integrate procedures defined at top-level, however, since code that assigns top-level variables can be introduced into the system (via eval or load) at any time. define-integrable can be used to force the integration of procedures bound at top-level, even if the integration of locally bound procedures is left to the compiler. It can also be used to force the integration of large procedures that the compiler would not normally integrate. (The expand/optimize procedure is useful for determining when integration does or does not take place.)

Section 11.2. Syntax-Rules Transformers

Chez Scheme extends syntax-rules to permit clause to include fenders just like those allowed within syntax-case clauses.

syntax: (syntax-rules (literal ...) clause ...)
returns: a transformer
libraries: (chezscheme)

Each literal must be an identifier other than an underscore ( _ ) or ellipsis ( ... ). Each clause must take the form below.

(pattern template)
(pattern fender template)

The first form is the only form supported by the Revised6 Report.

Section 11.3. Syntax-Case Transformers

Chez Scheme provides several procedures and syntactic forms that may be used to simplify the coding of certain syntactic abstractions.

procedure: (syntax->list syntax-object)
returns: a list of syntax objects
libraries: (chezscheme)

This procedure takes a syntax object representing a list-structured form and returns a list of syntax objects, each representing the corresponding subform of the input form.

syntax->list may be defined as follows.

(define syntax->list
  (lambda (ls)
    (syntax-case ls ()
      [() '()]
      [(x . r) (cons #'x (syntax->list #'r))])))

#'(a b c) <graphic> #<syntax (a b c)>
(syntax->list #'(a b c)) <graphic> (#<syntax a> #<syntax b> #<syntax c>)

syntax->list is not required for list structures constructed from individual pattern variable values or sequences of pattern-variable values, since such structures are already lists. For example:

(list? (with-syntax ([x #'a] [y #'b] [z #'c]) #'(x y z)))) <graphic> #t
(list? (with-syntax ([(x ...) #'(a b c)]) #'(x ...))) <graphic> #t

procedure: (syntax->vector syntax-object)
returns: a list of syntax objects
libraries: (chezscheme)

This procedure takes a syntax object representing a vector-structured form and returns a list of syntax objects, each representing the corresponding subform of the input form.

syntax->vector may be defined as follows.

(define syntax->vector
  (lambda (v)
    (syntax-case v ()
      [#(x ...) (apply vector (syntax->list #'(x ...)))])))

#'#(a b c) <graphic> #<syntax #(a b c)>
(syntax->vector #'#(a b c)) <graphic> #(#<syntax a> #<syntax b> #<syntax c>)

syntax->vector is not required for vector structures constructed from individual pattern variable values or sequences of pattern-variable values, since such structures are already vectors. For example:

(vector? (with-syntax ([x #'a] [y #'b] [z #'c]) #'#(x y z)))) <graphic> #t
(vector? (with-syntax ([(x ...) #'(a b c)]) #'#(x ...))) <graphic> #t

procedure: (syntax-object->datum obj)
returns: obj stripped of syntactic information
libraries: (chezscheme)

syntax-object->datum is identical to the Revised6 Report syntax->datum.

syntax: (datum template)
returns: see below
libraries: (chezscheme)

(datum template) is a convenient shorthand syntax for

(syntax->datum (syntax template))

datum may be defined simply as follows.

(define-syntax datum
  (syntax-rules ()
    [(_ t) (syntax->datum #'t)]))

(with-syntax ((a #'(a b c))) (datum a)) <graphic> (a b c)

procedure: (datum->syntax-object template-identifier obj)
returns: a syntax object
libraries: (chezscheme)

datum->syntax-object is identical to the Revised6 Report datum->syntax.

syntax: (with-implicit (id0 id1 ...) body1 body2 ...)
returns: see below
libraries: (chezscheme)

This form abstracts over the common usage of datum->syntax for creating implicit identifiers (see above). The form

(with-implicit (id0 id1 ...)
  body1 body2 ...)

is equivalent to

(with-syntax ([id1 (datum->syntax #'id0 'id1)] ...)
  body1 body2 ...)

with-implicit can be defined simply as follows.

(define-syntax with-implicit
  (syntax-rules ()
    [(_ (tid id ...) b1 b2 ...)
     (with-syntax ([id (datum->syntax #'tid 'id)] ...)
       b1 b2 ...)]))

We can use with-implicit to simplify the (correct version of) loop above.

(define-syntax loop
  (lambda (x)
    (syntax-case x ()
      [(k e ...)
       (with-implicit (k break)
         #'(call-with-current-continuation
             (lambda (break)
               (let f () e ... (f)))))])))

syntax: (include path)
returns: unspecified
libraries: (chezscheme)

path must be a string. include expands into a begin expression containing the forms found in the file named by path. For example, if the file f-def.ss contains (define f (lambda () x)), the expression

(let ([x "okay"])
  (include "f-def.ss")
  (f))

evaluates to "okay". An include form is treated as a definition if it appears within a sequence of definitions and the forms on the file named by path are all definitions, as in the above example. If the file contains expressions instead, the include form is treated as an expression.

include may be defined portably as follows, although Chez Scheme uses an implementation-dependent definition that allows it to capture and maintain source information for included code.

(define-syntax include
  (lambda (x)
    (define read-file
      (lambda (fn k)
        (let ([p (open-input-file fn)])
          (let f ([x (read p)])
            (if (eof-object? x)
                (begin (close-input-port p) '())
                (cons (datum->syntax k x)
                      (f (read p))))))))
    (syntax-case x ()
      [(k filename)
       (let ([fn (datum filename)])
         (with-syntax ([(exp ...) (read-file fn #'k)])
           #'(begin exp ...)))])))

The definition of include uses datum->syntax to convert the objects read from the file into syntax objects in the proper lexical context, so that identifier references and definitions within those expressions are scoped where the include form appears.

In Chez Scheme's implementation of include, the parameter source-directories (Section 12.5) determines the set of directories searched for source files not identified by absolute path names.

procedure: (syntax-error obj string ...)
returns: does not return
libraries: (chezscheme)

Syntax errors may be reported with syntax-error, which produces a message by concatenating string ... and a printed representation of obj. If no string arguments are provided, the string "invalid syntax" is used instead. When obj is a syntax object, the syntax-object wrapper is stripped (as with syntax->datum) before the printed representation is created. If source file information is present in the syntax-object wrapper, syntax-error incorporates this information into the error message.

syntax-case and syntax-rules call syntax-error automatically if the input fails to match one of the clauses.

We can use syntax-error to precisely report the cause of the errors detected in the following definition of (unnamed) let.

(define-syntax let
  (lambda (x)
    (define check-ids!
      (lambda (ls)
        (unless (null? ls)
          (unless (identifier? (car ls))
            (syntax-error (car ls) "let cannot bind non-identifier"))
          (check-ids! (cdr ls)))))
    (define check-unique!
      (lambda (ls)
        (unless (null? ls)
          (let ([x (car ls)])
            (when (let mem? ([ls (cdr ls)])
                    (and (not (null? ls))
                         (or (bound-identifier=? x (car ls))
                             (mem? (cdr ls)))))
              (syntax-error x "let cannot bind two occurrences of")))
          (check-unique! (cdr ls)))))
    (syntax-case x ()
      [(_ ((i e) ...) b1 b2 ...)
       (begin
         (check-ids! #'(i ...))
         (check-unique! #'(i ...))
         #'((lambda (i ...) b1 b2 ...) e ...))])))

With this change, the expression

(let ([a 3] [a 4]) (+ a a))

produces the error message "let cannot bind two occurrences of a."

procedure: (literal-identifier=? identifier1 identifier2)
returns: see below
libraries: (chezscheme)

This procedure is identical to the Revised6 Report free-identifier=?, and is provided for backward compatibility only.

Section 11.4. Compile-time Values and Properties

When defining sets of dependent macros, it is often convenient to attach information to identifiers in the same compile time environment that the expander uses to record information about variables, keywords, module names, etc. For example, a record-type definition macro, like define-record-type, might need to attach information to the record-type name in the compile-time environment for use in handling child record-type definitions.

Chez Scheme provides two mechanisms for attaching information to identifiers in the compile-time environment: compile-time values and compile-time properties. A compile-time value is a kind of transformer that can be associated with an identifier via define-syntax, let-syntax, letrec-syntax, and fluid-let-syntax. When an identifier is associated with a compile-time value, it cannot also have any other meaning, and an attempt to reference it as an ordinary identifier results in a syntax error. A compile-time property, on the other hand, is maintained alongside an existing binding, providing additional information about the binding. Properties are ignored when ordinary references to an identifier occur.

The mechanisms used by a macro to obtain compile-time values and properties are similar. In both cases, the macro's transformer returns a procedure p rather than a syntax object. The expander invokes p with one argument, an environment-lookup procedure lookup, which p can then use to obtain compile-time values and properties for one or more identifiers before it constructs the macro's final output. lookup accepts one or two identifier arguments. With one argument, id, lookup returns the compile-time value of id, or #f if id has no compile-time value. With two arguments, id and key, lookup returns the value of id's key property, or #f if id has no key property.

procedure: (make-compile-time-value obj)
returns: a compile-time value
libraries: (chezscheme)

A compile time value is a kind of transformer with which a keyword may be associated by any of the keyword binding constructs, e.g., define-syntax or let-syntax. The transformer encapsulates the supplied obj. The encapsulated object may be retrieved as described above.

The following example illustrates how this feature might be used to define a simple syntactic record-definition mechanism where the record type descriptor is generated at expansion time.

(define-syntax drt
  (lambda (x)
    (define construct-name
      (lambda (template-identifier . args)
        (datum->syntax template-identifier
          (string->symbol
            (apply string-append
              (map (lambda (x)
                     (if (string? x)
                         x
                         (symbol->string (syntax->datum x))))
                   args))))))
    (define do-drt
      (lambda (rname fname* prtd)
        (with-syntax ([rname rname]
                      [rtd (make-record-type-descriptor
                             (syntax->datum rname) prtd #f #f #f
                             (list->vector
                               (map (lambda (fname)
                                      `(immutable ,(syntax->datum fname)))
                                    fname*)))]
                      [make-rname (construct-name rname "make-" rname)]
                      [rname? (construct-name rname rname "?")]
                      [(rname-fname ...)
                       (map (lambda (fname)
                              (construct-name fname rname "-" fname))
                            fname*)]
                      [(i ...) (enumerate fname*)])
          #'(begin
              (define-syntax rname (make-compile-time-value 'rtd))
              (define rcd (make-record-constructor-descriptor 'rtd #f #f))
              (define make-rname (record-constructor rcd))
              (define rname? (record-predicate 'rtd))
              (define rname-fname (record-accessor 'rtd i))
              ...))))
    (syntax-case x (parent)
      [(_ rname (fname ...))
       (for-all identifier? #'(rname fname ...))
       (do-drt #'rname #'(fname ...) #f)]
      [(_ rname pname (fname ...))
       (for-all identifier? #'(rname pname fname ...))
       (lambda (lookup)
         (let ([prtd (lookup #'pname)])
           (unless (record-type-descriptor? prtd)
             (syntax-error #'pname "unrecognized parent record type"))
           (do-drt #'rname #'(fname ...) prtd)))])))

(drt prec (x y))
(drt crec prec (z))
(define r (make-crec 1 2 3))
(prec? r) <graphic> #t
(prec-x r) <graphic> 1
(crec-z r) <graphic> 3
prec <graphic> exception: invalid syntax prec

syntax: (define-property id key expr)
returns: unspecified
libraries: (chezscheme)

A define-property form attaches a property to an existing identifier binding without disturbing the existing meaning of the identifier in the scope of that binding. It is typically used by one macro to record information about a binding for use by another macro. Both id and key must be identifiers. The expression expr is evaluated when the define-property form is expanded, and a new property associating key with the value of expr is attached to the existing binding of id, which must have a visible local or top-level binding.

define-property is a definition and can appear anywhere other definitions can appear. The scope of a property introduced by define-property is the entire body in which the define-property form appears or global if it appears at top level, except where it is replaced by a property for the same id and key or where the binding to which it is attached is shadowed. Any number of properties can be attached to the same binding with different keys. Attaching a new property with the same name as an property already attached to a binding shadows the existing property with the new property.

The following example defines a macro, get-info, that retrieves the info property of a binding, defines the variable x, attaches an info property to the binding of x, retrieves the property via get-info, references x to show that its normal binding is still intact, and uses get-info again within the scope of a different binding of x to show that the properties are shadowed as well as the outer binding of x.

(define info)
(define-syntax get-info
  (lambda (x)
    (lambda (lookup)
      (syntax-case x ()
        [(_ q)
         (let ([info-value (lookup #'q #'info)])
           #`'#,(datum->syntax #'* info-value))]))))
(define x "x-value")
(define-property x info "x-info")
(get-info x) <graphic> "x-info"
<graphic> "x-value"
(let ([x "inner-x-value"]) (get-info x)) <graphic> #f

For debugging, it is often useful to have a form that retrieves an arbitrary property, given an identifier and a key. The get-property macro below does just that.

(define-syntax get-property
  (lambda (x)
    (lambda (r)
      (syntax-case x ()
        [(_ id key)
         #`'#,(datum->syntax #'* (r #'id #'key))]))))
(get-property x info) <graphic> "x-info"

The bindings for both identifiers must be visible where get-property is used.

The version of drt defined below is like the one defined using make-compile-time-value above, except that it defines the record name as a macro that raises an exception with a more descriptive message, while attaching the record type descriptor to the binding as a separate property. The variable drt-key defined along with drt is used only as the key for the property that drt attaches to a record name. Both drt-key and drt are defined within a module that exports only the latter, ensuring that the properties used by drt cannot be accessed or forged.

(library (drt) (export drt) (import (chezscheme))
  (define drt-key)
  (define-syntax drt
    (lambda (x)
      (define construct-name
        (lambda (template-identifier . args)
          (datum->syntax template-identifier
            (string->symbol
              (apply string-append
                (map (lambda (x)
                       (if (string? x)
                           x
                           (symbol->string (syntax->datum x))))
                     args))))))
      (define do-drt
        (lambda (rname fname* prtd)
          (with-syntax ([rname rname]
                        [rtd (make-record-type-descriptor
                               (syntax->datum rname) prtd #f #f #f
                               (list->vector
                                 (map (lambda (fname)
                                        `(immutable ,(syntax->datum fname)))
                                      fname*)))]
                        [make-rname (construct-name rname "make-" rname)]
                        [rname? (construct-name rname rname "?")]
                        [(rname-fname ...)
                         (map (lambda (fname)
                                (construct-name fname rname "-" fname))
                              fname*)]
                        [(i ...) (enumerate fname*)])
            #'(begin
                (define-syntax rname
                  (lambda (x)
                    (syntax-error x "invalid use of record name")))
                (define rcd (make-record-constructor-descriptor 'rtd #f #f))
                (define-property rname drt-key 'rtd)
                (define make-rname (record-constructor rcd))
                (define rname? (record-predicate 'rtd))
                (define rname-fname (record-accessor 'rtd i))
                ...))))
      (syntax-case x (parent)
        [(_ rname (fname ...))
         (for-all identifier? #'(rname fname ...))
         (do-drt #'rname #'(fname ...) #f)]
        [(_ rname pname (fname ...))
         (for-all identifier? #'(rname pname fname ...))
         (lambda (lookup)
           (let ([prtd (lookup #'pname #'drt-key)])
             (unless prtd
               (syntax-error #'pname "unrecognized parent record type"))
             (do-drt #'rname #'(fname ...) prtd)))]))))

(import (drt))
(drt prec (x y))
(drt crec prec (z))
(define r (make-crec 1 2 3))
(prec? r) <graphic> #t
(prec-x r) <graphic> 1
(crec-z r) <graphic> 3
prec <graphic> exception: invalid use of record name prec

Section 11.5. Modules

Modules are used to help organize programs into separate parts that interact cleanly via declared interfaces. Although modular programming is typically used to facilitate the development of large programs possibly written by many individuals, it may also be used in Chez Scheme at a "micro-modular" level, since Chez Scheme module and import forms are definitions and may appear anywhere any other kind of definition may appear, including within a lambda body or other local scope.

Modules control visibility of bindings and can be viewed as extending lexical scoping to allow more precise control over where bindings are or are not visible. Modules export identifier bindings, i.e., variable bindings, keyword bindings, or module name bindings. Modules may be named or anonymous. Bindings exported from a named module may be made visible via an import form wherever the module's name is visible. Bindings exported from an anonymous module are implicitly imported where the module form appears. Anonymous modules are useful for hiding some of a set of bindings while allowing the remaining bindings in the set to be visible.

Some of the text and examples given in this section are adapted from the paper "Extending the scope of syntactic abstraction" [31], which describes modules and their implementation in more detail.

syntax: (module name interface defn ... init ...)
syntax: (module interface defn ... init ...)
returns: unspecified
libraries: (chezscheme)

name is an identifier, defn ... are definitions, and init ... are expressions. interface is a list of exports (export ...), where each export is either an identifier identifier or of the form (identifier export ...).

The first syntax for module establishes a named scope that encapsulates a set of identifier bindings. The exported bindings may be made visible via import or import-only (Section 10.4) anywhere the module name is visible. The second syntax for module introduces an anonymous module whose bindings are implicitly imported (as if by import of a hidden module name) where the module form appears.

A module consists of a (possibly empty) set of definitions and a (possibly empty) sequence of initialization expressions. The identifiers defined within a module are visible within the body of the module and, if exported, within the scope of an import for the module. Each identifier listed in a module's interface must be defined within or imported into that module. A module form is a definition and can appear anywhere other definitions can appear, including at the top level of a program, nested within the bodies of lambda expressions, nested within library and top-level program forms, and nested within other modules. Also, because module names are scoped like other identifiers, modules and libraries may export module names as well as variables and keywords.

When an interface contains an export of the form (identifier export ...), only identifier is visible in the importing context. The identifiers within export ... are indirect imports, as if declared via an indirect-export form (Section 10.4).

Module names occupy the same namespace as other identifiers and follow the same scoping rules. Unless exported, identifiers defined within a module are visible only within that module.

Expressions within a module can reference identifiers bound outside of the module.

(let ([x 3])
  (module m (plusx)
    (define plusx (lambda (y) (+ x y))))
  (import m)
  (let ([x 4])
    (plusx 5))) <graphic> 8

Similarly, import does not prevent access to identifiers that are visible where the import form appears, except for those variables shadowed by the imported identifiers.

(module m (y) (define y 'm-y))
(let ([x 'local-x] [y 'local-y])
  (import m)
  (list x y)) <graphic> (local-x m-y)

On the other hand, use of import-only within a module establishes an isolated scope in which the only visible identifiers are those exported by the imported module.

(module m (y) (define y 'm-y))
(let ([x 'local-x] [y 'local-y])
  (import-only m)
  x) <graphic> Error: x is not visible

This is sometimes desirable for static verification that no identifiers are used except those explicitly imported into a module or local scope.

Unless a module imported via import-only exports import or import-only and the name of at least one module, subsequent imports within the scope of the import-only form are not possible. To create an isolated scope containing the exports of more than one module without making import or import-only visible, all of the modules to be imported must be listed in the same import-only form.

Another solution is to create a single module that contains the exports of each of the other modules.

(module m2 (y) (define y 'y))
(module m1 (x) (define x 'x))
(module mega-module (cons x y)
  (import m1)
  (import m2)
  (import scheme))
(let ([y 3])
  (import-only mega-module)
  (cons x y)) <graphic> (x . y)

Before it is compiled, a source program is translated into a core language program containing no syntactic abstractions, syntactic definitions, library definitions, module definitions, or import forms. Translation is performed by a syntax expander that processes the forms in the source program via recursive descent.

A define-syntax form associates a keyword with a transformer in a translation-time environment. When the expander encounters a keyword, it invokes the associated transformer and reprocesses the resulting form. A module form associates a module name with an interface. When the expander encounters an import form, it extracts the corresponding module interface from the translation-time environment and makes the exported bindings visible in the scope where the import form appears.

Internal definitions and definitions within a module body are processed from left to right so that a module's definition and import may appear within the same sequence of definitions. Expressions appearing within a body and the right-hand sides of variable definitions, however, are translated only after the entire set of definitions has been processed, allowing full mutual recursion among variable and syntactic definitions.

Module and import forms affect only the visibility of identifiers in the source program, not their meanings. In particular, variables are bound to locations whether defined within or outside of a module, and import does not introduce new locations. Local variables are renamed as necessary to preserve the scoping relationships established by both modules and syntactic abstractions. Thus, the expression:

(let ([x 1])
  (module m (x setter)
    (define-syntax x (identifier-syntax z))
    (define setter (lambda (x) (set! z x)))
    (define z 5))
  (let ([y x] [z 0])
    (import m)
    (setter 3)
    (+ x y z))) <graphic> 4

is equivalent to the following program in which identifiers have been consistently renamed as indicated by subscripts.

(let ([x0 1])
  (define-syntax x1 (identifier-syntax z1))
  (define setter1 (lambda (x2) (set! z1 x2)))
  (define z1 5)
  (let ([y3 x0] [z3 0])
    (setter1 3)
    (+ x1 y3 z3)))

Definitions within a top-level begin, lambda, top-level program, library, or module body are processed from left to right by the expander at expand time, and the variable definitions are evaluated from left-to-right at run time. Initialization expressions appearing within a module body are evaluated in sequence after the evaluation of the variable definitions.

Mutually recursive modules can be defined in several ways. In the following program, a and b are mutually recursive modules exported by an anonymous module whose local scope is used to statically link the two. For example, the free variable y within module a refers to the binding for y, provided by importing b, in the enclosing module.

(module (a b)
  (module a (x) (define x (lambda () y)))
  (module b (y) (define y (lambda () x)))
  (import a)
  (import b))

The following syntactic abstraction generalizes this pattern to permit the definition of multiple mutually recursive modules.

(define-syntax rec-modules
  (syntax-rules (module)
    [(_ (module m (id ...) form ...) ...)
     (module (m ...)
       (module m (id ...) form ...) ...
       (import m) ...)]))

Because a module can re-export imported bindings, it is quite easy to provide multiple views on a single module, as s and t provide for r below, or to combine several modules into a compound, as r does.

(module p (x y)
  (define x 1) (define y 2))
(module q (y z)
  (define y 3) (define z 4))
(module r (a b c d)
  (import* p (a x) (b y))
  (import* q (c y) (d z)))
(module s (a c) (import r))
(module t (b d) (import r))

To allow interfaces to be separated from implementations, the following syntactic abstractions support the definition and use of named interfaces.

(define-syntax define-interface
  (syntax-rules ()
    [(_ name (export ...))
     (define-syntax name
       (lambda (x)
         (syntax-case x ()
           [(_ n defs)
            (with-implicit (n export ...)
              #'(module n (export ...) .
                  defs))])))]))

(define-syntax define-module
  (syntax-rules ()
    [(_ name interface defn ...)
     (interface name (defn ...))]))

define-interface creates an interface macro that, given a module name and a list of definitions, expands into a module definition with a concrete interface.

with-implicit is used to ensure that the introduced export identifiers are visible in the same scope as the name of the module in the define-module form.

define-interface and define-module can be used as follows.

(define-interface simple (a b))
(define-module m simple
  (define-syntax a (identifier-syntax 1))
  (define b (lambda () c))
  (define c 2))
(let () (import m) (+ a (b))) <graphic> 3

The abstract module facility defined below allows a module interface to be satisfied incrementally when module forms are evaluated. This permits flexibility in the separation between the interface and implementation, supports separate compilation of mutually recursive modules, and permits redefinition of module implementations.

(define-syntax abstract-module
  (syntax-rules ()
    [(_ name (ex ...) (kwd ...) defn ...)
     (module name (ex ... kwd ...)
       (declare ex) ...
       defn ...)]))

(define-syntax implement
  (syntax-rules ()
    [(_ name form ...)
     (module () (import name) form ...)]))

Within an abstract-module form, each of the exports in the list ex ... must be variables. The values of these variables are supplied by one or more separate implement forms. Since keyword bindings must be present at compile time, they cannot be satisfied incrementally and are instead listed as separate exports and defined within the abstract module.

Within an implement form, the sequence of forms form ... is a sequence of zero or more definitions followed by a sequence of zero or more expressions. Since the module used in the expansion of implement does not export anything, the definitions are all local to the implement form. The expressions may be arbitrary expressions, but should include one satisfy form for each variable whose definition is supplied by the implement form. A satisfy form has the syntax

(satisfy variable expr)

declare and satisfy may simply be the equivalents of define and set!.

(define-syntax declare (identifier-syntax define))
(define-syntax satisfy (identifier-syntax set!))

Alternatively, declare can initialize the declared variable to the value of a flag known only to declare and satisfy, and satisfy can verify that this flag is still present to insure that only one attempt to satisfy the value of a given identifier is made.

(module ((declare cookie) (satisfy cookie))
  (define cookie "chocolate chip")
  (define-syntax declare
    (syntax-rules () [(_ var) (define var cookie)]))
  (define-syntax satisfy
    (syntax-rules ()
      [(_ var exp)
       (if (eq? var cookie)
           (set! var exp)
           (assertion-violationf 'satisfy
             "value of variable ~s has already been satisfied"
             'var))])))

Using abstract-module and implement, we can define mutually recursive and separately compilable modules as follows.

(abstract-module e (even?) (pred)
  (define-syntax pred
    (syntax-rules () [(_ exp) (- exp 1)])))

(abstract-module o (odd?) ())

(implement e
  (import o)
  (satisfy even?
    (lambda (x)
      (or (zero? x) (odd? (pred x))))))

(implement o
  (import e)
  (satisfy odd?
    (lambda (x) (not (even? x)))))

(let () (import-only e) (even? 38)) <graphic> #t

syntax: only
syntax: except
syntax: add-prefix
syntax: drop-prefix
syntax: rename
syntax: alias
libraries: (chezscheme)

These identifiers are auxiliary keywords for import and import-only. It is a syntax violation to reference these identifiers except in contexts where they are recognized as auxiliary keywords.

Section 11.6. Standalone import and export forms

The local import and export forms described in Section 10.4 can be used equally well for and within modules.

Section 11.7. Built-in Modules

Five modules are built-in to Chez Scheme: scheme, r5rs, r5rs-syntax, ieee, and $system. Each module is immutable, i.e., the exported bindings cannot be altered.

module: scheme
libraries: (chezscheme)

scheme contains all user-visible top-level bindings (variables, keywords, and module names) built into Chez Scheme.

module: r5rs
libraries: (chezscheme)

r5rs contains all top-level bindings (variables and keywords) defined in the Revised5 Report on Scheme. The bindings exported from r5rs are precisely those that are available within an expression evaluated via eval with the environment specifier returned by scheme-report-environment.

module: r5rs-syntax
libraries: (chezscheme)

r5rs-syntax contains all top-level keyword bindings defined in the Revised5 Report on Scheme. The bindings exported from r5rs-syntax are precisely those that are available within an expression evaluated via eval with the environment specifier returned by null-environment.

module: ieee
libraries: (chezscheme)

ieee contains all top-level bindings (variables and keywords) defined in the ANSI/IEEE standard for Scheme. The bindings exported from ieee are precisely those that are available within an expression evaluated via eval with the environment specifier returned by ieee-environment.

module: $system
libraries: (chezscheme)

$system contains all user-visible top-level bindings built into Chez Scheme along with various undocumented system bindings.

Section 11.8. Meta Definitions

syntax: (meta . definition)
returns: unspecified
libraries: (chezscheme)

The meta keyword is actually a prefix that can be placed in front of any definition keyword, e.g.,

(meta define x 3)

It tells the expander that any variable definition resulting from the definition is to be an expand-time definition available only to the right-hand sides of other meta definitions and, most importantly, transformer expressions. It is used to define expand-time helpers and other information for use by one or more syntax-case transformers.

(module M (helper1 a b)
  (meta define helper1
    (lambda (---)
      ---))
  (meta define helper2
    (lambda (---)
      --- (helper2 ---) ---))
  (define-syntax a
    (lambda (x)
      --- (helper1 ---) ---))
  (define-syntax b
    (lambda (x)
      --- (helper1 ---) ---
      --- (helper2 ---) ---)))

The right-hand-side expressions of a syntax definition or meta definition can refer only to identifiers whose values are already available in the compile-time environment. Because of the left-to-right expansion order for library, module, lambda, and similar bodies, this implies a semantics similar to let* for a sequence of meta definitions, in which each right-hand side can refer only to the variables defined earlier in the sequence. An exception is that the right-hand side of a meta definition can refer to its own name as long as the reference is not evaluated until after the value of the expression has been computed. This permits meta definitions to be self-recursive but not mutually recursive. The right-hand side of a meta definition can, however, build syntax objects containing occurrences of any identifiers defined in the body in which the meta definition appears.

Meta definitions propagate through macro expansion, so one can write, for example:

(module (a)
  (meta define-record foo (x))
  (define-syntax a
    (let ([q (make-foo #''q)])
      (lambda (x) (foo-x q)))))
<graphic> q

where define-record is a macro that expands into a set of defines.

It is also sometimes convenient to write

(meta begin defn ...)

or

(meta module {exports} defn ...)

or

(meta include "path")

to create groups of meta bindings.

Section 11.9. Conditional expansion

Expansion-time decisions can be made via meta-cond, which is similar to cond but evaluates the test expressions at expansion time and can be used in contexts where definitions are expected as well as in expression contexts.

syntax: (meta-cond clause1 clause2 ...)
returns: see below
libraries: (chezscheme)

Each clause but the last must take the form:

(test expr1 expr2 ...)

The last may take the same form or be an else clause of the form:

(else expr1 expr2 ...)

During expansion, the test expressions are evaluated in order until one evaluates to a true value or until all of the tests have been evaluated. If a test evaluates to a true value, the meta-cond form expands to a begin form containing the corresponding expressions expr1 expr2 .... If no test evaluates to a true value and an else clause is present, the meta-cond form expands to a begin form containing the expressions expr1 expr2 ... from the else clause. Otherwise the meta-cond expression expands into a call to the void procedure.

meta-cond might be defined as follows.

(define-syntax meta-cond
  (syntax-rules ()
    [(_ [a0 a1 a2 ...] [b0 b1 b2 ...] ...)
     (let-syntax ([expr (cond
                          [a0 (identifier-syntax (begin a1 a2 ...))]
                          [b0 (identifier-syntax (begin b1 b2 ...))]
                          ...)])
       expr)]))

meta-cond is used to choose, at expansion time, from among a set of possible forms. For example, one might have safe (error-checking) and unsafe (non-error-checking) versions of a procedure and decide which to call based on the compile-time optimization level, as shown below.

(meta-cond
  [(= (optimize-level) 3) (unsafe-frob x)]
  [else (safe-frob x)])

Section 11.10. Aliases

syntax: (alias id1 id2)
returns: unspecified
libraries: (chezscheme)

alias is a definition and can appear anywhere other definitions can appear. It is used to transfer the binding from one identifier to another.

(let ([x 3]) (alias y x) (set! y 4) (list x y)) <graphic> (4 4)

(module lisp (if)
  (module (scheme:if)
    (import scheme)
    (alias scheme:if if))
  (define-syntax if
    (syntax-rules ()
      [(_ e_1 e_2 e_3)
       (scheme:if (not (memq e_1 '(#f ()))) e_2 e_3)])))
(define (length ls)
  (import lisp)
  (if ls (+ (length (cdr ls)) 1) 0))
(length '(a b c)) <graphic> 3

Because of left-to-right expansion order, aliases should appear after the definition of the right-hand-side identifier, e.g.:

(let ()
  (import-only (chezscheme))
  (define y 3)
  (alias x y)
  x) <graphic> 3

rather than:

(let ()
  (import-only (chezscheme))
  (alias x y)
  (define y 3)
  x) <graphic> exception: unbound identifier

Section 11.11. Annotations

When source code is read from a file by load, compile-file, or variants of these, such as load-library, the reader attaches annotations to each object read from the file. These annotations identify the file and the position of the object within the file. Annotations are tracked through the compilation process and associated with compiled code at run time. The expander and compiler use the annotations to produce syntax errors and compiler warnings that identify the location of the offending form, and the inspector uses them to identify the locations of calls and procedure definitions.

While these annotations are usually maintained "behind the scenes," the programmer can manipulate them directly via a set of routines for creating and accessing annotations.

Annotations are values of a type distinct from other types and have three components: an expression, possibly with annotated subexpressions, a source object, and a stripped version of the expression. Annotations can be created via make-annotation, which takes three arguments corresponding to the three components. The second argument must be a source object, and the third argument should be a stripped version of the first argument, i.e., equivalent to the first argument with each annotation replaced by its expression component. An annotation is essentially equivalent to its stripped component as a representation of source code, with the source information attached and available to the expander or evaluator.

Source objects are also values of a type distinct from other types and also have three components: a source-file descriptor (sfd), a beginning file position (bfp), and an ending file position (efp). The sfd identifies the file from which an expression is read and the bfp identify the range of character positions occupied by the object in the file, with the bfp being inclusive and the efp being exclusive. A source object can be created via make-source-object, which takes three arguments corresponding to these components. The first argument must be a source-file descriptor, the second and third must be nonnegative exact integers, and the second must not be greater than the third.

Source-file descriptors are also values of a type distinct from all other types and have two components: the file's path, represented by a string, and a checksum, represented by a number. The path might or might not be an absolute path depending on how the file's path was specified when the source-file descriptor was created. The checksum is computed based on the file's length and contents when the file is created and checked by tools that look for the source file to make sure that the proper file has been found and has not been modified. Source-file descriptors can be created with make-source-file-descriptor, which accepts two arguments: a string naming the path and a binary input port, along with an optional third boolean argument, reset?, which defaults to false. make-source-file-descriptor computes a checksum based on the contents of the port, starting at its current position. It resets the port, using set-port-position!, after computing the checksum if reset? is true; otherwise, it leaves the port at end-of-file.

The procedures that create, check for, and access annotations, source objects, and source-file descriptors are summarized below and described in more detail later in this section.

(make-annotation obj source-object obj<graphic> annotation
(annotation? obj<graphic> boolean
(annotation-expression annotation<graphic> obj
(annotation-source annotation<graphic> source-object
(annotation-stripped annotation<graphic> obj

(make-source-object sfd uint uint<graphic> source-object
(source-object? obj<graphic> boolean
(source-object-bfp source-object<graphic> uint
(source-object-efp source-object<graphic> uint
(source-object-sfd source-object<graphic> sfd

(make-source-file-descriptor string binary-input-port<graphic> sfd
(make-source-file-descriptor string binary-input-port reset?<graphic> sfd
(source-file-descriptor? obj<graphic> boolean
(source-file-descriptor-checksum sfd<graphic> obj
(source-file-descriptor-path sfd<graphic> obj

A program might open a source file with open-file-input-port, create an sfd using make-source-file-descriptor, create a textual port from the binary port using transcoded-port, and create source objects and annotations for each of the objects it reads from the file. If a custom reader is not required, the Scheme reader can be used to read annotations via the get-datum/annotations procedure:

(get-datum/annotations textual-input-port sfd uint<graphic> objuint

get-datum/annotations is like get-datum but instead of returning a plain datum, it returns an annotation encapsulating a datum (possibly with nested annotations), a source object, and the plain (stripped) datum. It also returns a second value, the position of the first character beyond the object in the file. Character positions are accepted and returned by get-datum/annotations so that the textual port need not support port-position and need not report positions in characters if it does support port-position. (Positions are usually reported in bytes.) The bfp and efp positions recorded in the annotations returned by get-datum/annotations are correct only if the positions supplied to it are correct.

Once read, an annotation can be passed to the expander, interpreter, or compiler. The procedures eval, expand, interpret, and compile all accept annotated or unannotated input.

Two additional procedures complete the set of annotation-related primitives:

(open-source-file sfd<graphic> #f or port
(syntax->annotation obj<graphic> #f or annotation

open-source-file attempts to locate and open the source file identified by sfd. It returns a textual input port, positioned at the beginning of the file, if successful, and #f otherwise.

syntax->annotation accepts a syntax object. If the syntax object's expression is annotated, it returns the annotation; otherwise, it returns #f. It can be used by a macro to extract source information, when available, from an input form.

The procedure datum->syntax accepts either an annotated or unannotated input datum.

procedure: (make-annotation obj source-object stripped-obj)
returns: an annotation
libraries: (chezscheme)

The annotation is formed with obj as its expression component, source-object as its source-object component, and stripped-obj as its stripped component. obj should represent an expression, possibly with embedded annotations. stripped-obj should be a stripped version of obj, i.e., equivalent to obj with each annotation replaced by its expression component.

procedure: (annotation? obj)
returns: #t if obj is an annotation, otherwise #f
libraries: (chezscheme)

procedure: (annotation-expression annotation)
returns: the expression component of annotation
libraries: (chezscheme)

procedure: (annotation-source annotation)
returns: the source-object component of annotation
libraries: (chezscheme)

procedure: (annotation-stripped annotation)
returns: the stripped component of annotation
libraries: (chezscheme)

procedure: (make-source-object sfd bfp efp)
returns: a source-object
libraries: (chezscheme)

sfd must be a source-file descriptor. bfp and efp must be exact nonnegative integers, and bfp should not be greater than efp.

procedure: (source-object? obj)
returns: #t if obj is a source object, otherwise #f
libraries: (chezscheme)

procedure: (source-object-bfp source-object)
returns: the bfp component of source-object
libraries: (chezscheme)

procedure: (source-object-efp source-object)
returns: the efp component of source-object
libraries: (chezscheme)

procedure: (source-object-sfd source-object)
returns: the sfd component of source-object
libraries: (chezscheme)

procedure: (make-source-file-descriptor string binary-input-port)
procedure: (make-source-file-descriptor string binary-input-port reset?)
returns: a source-file descriptor
libraries: (chezscheme)

To compute the checksum encapsulated in the source-file descriptor, this procedure must read all of the data from binary-input-port. If reset? is present and #t, the port is reset to its original position, as if via port-position. Otherwise, it is left pointing at end-of-file.

procedure: (source-file-descriptor? obj)
returns: #t if obj is a source-file descriptor, otherwise #f
libraries: (chezscheme)

procedure: (source-file-descriptor-checksum sfd)
returns: the checksum component of sfd
libraries: (chezscheme)

procedure: (source-file-descriptor-path sfd)
returns: the path component of sfd
libraries: (chezscheme)

sfd must be a source-file descriptor.

procedure: (syntax->annotation obj)
returns: an annotation or #f
libraries: (chezscheme)

If obj is an annotation or syntax-object encapsulating an annotation, the annotation is returned.

procedure: (get-datum/annotations textual-input-port sfd bfp)
returns: see below
libraries: (chezscheme)

sfd must be a source-file descriptor. bfd must be an exact nonnegative integer and should be the character position of the next character to be read from textual-input-port.

This procedure returns two values: an annotated object and an ending file position. In most cases, bfp should be 0 for the first call to get-datum/annotation at the start of a file, and it should be the second return value of the preceding call to get-datum/annotation for each subsequent call. This protocol is necessary to handle files containing multiple-byte characters, since file positions do not necessarily correspond to character positions.

procedure: (open-source-file sfd)
returns: a port or #f
libraries: (chezscheme)

sfd must be a source-file descriptor. This procedure attempts to locate and open the source file identified by sfd. It returns a textual input port, positioned at the beginning of the file, if successful, and #f otherwise. It can fail even if a file with the correct name exists in one of the source directories when the file's checksum does not match the checksum recorded in sfd.

R. Kent Dybvig / Chez Scheme Version 8 User's Guide
Copyright © 2009 R. Kent Dybvig
Revised October 2011 for Chez Scheme Version 8.4
Cadence Research Systems / www.scheme.com
Cover illustration © 2010 Jean-Pierre Hébert
ISBN: 978-0-966-71392-3
about this book / purchase this book in print form