Chapter 10. Syntactic Extension

This chapter and Chapter 8 of The Scheme Programming Language, Third Edition contain much of the same text. Several additional features are described here, including the module system (Section 10.5), meta definitions (Section 10.7), conditional expansion (Section 10.8) syntax-rules fenders, literal-identifier?, identifier-syntax, and include. On the other hand, The Scheme Programming Language, Third Edition contains a section on examples (Section 8.4) that is not present here.

Syntactic extensions, or macros, are used to simplify and regularize repeated patterns in a program, to introduce syntactic forms with new evaluation rules, and to perform transformations that help make programs more efficient.

A syntactic extension typically takes the form (keyword subform ...), where keyword is the identifier that names the syntactic extension. The syntax of each subform varies from one syntactic extension to another. Syntactic extensions can also take the form of improper lists (or even singleton identifiers; see Section 10.4), although this is less common.

New syntactic extensions are defined by associating keywords with transformation procedures, or transformers. Syntactic extensions are defined globally using top-level define-syntax forms or within the scope of particular expressions using let-syntax, letrec-syntax, internal define-syntax, or fluid-let-syntax. Transformers are created using syntax-rules or syntax-case, which allow transformations to be specified via pattern matching.

The syntactic extension mechanisms described in this chapter are part of the "syntax-case" system that has become a de facto standard in the absence of a standard full-featured syntactic extension system. A portable implementation of the syntax-case system is available at http://www.scheme.com/syntax-case/. The syntax-case system also supports modules and several other features that are described in 10.5. A description of the motivations behind and implementation of the system can be found in the articles "Syntactic Abstraction in Scheme" [17] and "Extending the Scope of Syntactic Abstraction" [26].

The Revised5 Report covers let-syntax, letrec-syntax, top-level define-syntax, and syntax-rules only. The pattern language supported by the Revised5 Report version of syntax-rules is also more limited, with pattern ellipses allowed only at the end of list- or vector-structured patterns. (See page 212.) Furthermore, the bodies of let-syntax and letrec-syntax are treated like lambda bodies, i.e., they open up new scopes, which prevents them from being used in contexts where definitions are required. (See page 210.) Programmers desiring to write programs that are guaranteed to run in all Revised5 Report implementations should stick with the Revised5 Report subset and use let-syntax and letrec-syntax in a manner consistent with either interpretation.

Section 10.1. Expansion Process

Syntactic extensions are expanded into core forms at the start of evaluation (before compilation or interpretation) by a syntax expander. The expander is invoked once for each top-level form in a program. If the expander encounters a syntactic extension, it invokes the associated transformer to expand the syntactic extension, then repeats the expansion process for the form returned by the transformer. If the expander encounters a core syntactic form, it recursively processes the subforms, if any, and reconstructs the form from the expanded subforms. Information about identifier bindings is maintained during expansion to enforce lexical scoping for variables and keywords.

To handle internal definitions, the expander processes the initial forms in a lambda, let, or similar body from left to right. How the expander processes each form encountered as it does so depends upon the kind of form.

syntactic extension:
The expander invokes the associated transformer to expand the syntactic extension, then recursively performs whichever of these actions are appropriate for the resulting form.

define-syntax form:
The expander expands and evaluates the right-hand-side expression and binds the keyword to the resulting transformer.

module form:
The expander applies this process recursively, again deferring the expansion of the right-hand sides of any variable definitions and deferring the expansion of any expressions it finds, then binds the module identifier to a module interface describing the module's exports.

import form:
The expander determines the exports of the specified module(s) and makes them visible.

meta form:
The expander removes the meta prefix and performs whichever of these actions are appropriate for the resulting form, in "meta" mode.

define form (not in meta mode):
The expander records the fact that the defined identifier is a variable but defers expansion of the right-hand-side expression until after all of the definitions have been processed.

define form (meta mode):
The expander expands and evaluates the right-hand-side expression and binds the variable to the resulting value in a compile-time environment visible only to syntax definitions and the right-hand sides of other meta variable definitions.

alias form:
The expander establishes a binding for the new identifier to the aliased identifier.

begin form:
The expander splices the subforms into the list of body forms it is processing.

let-syntax or letrec-syntax form:
The expander splices the inner body forms into the list of (outer) body forms it is processing, arranging for the keywords bound by the let-syntax and letrec-syntax to be visible only in the inner body forms.

expression, i.e., nondefinition:
The expander completes the expansion of the deferred forms and the current and remaining expressions in the body.

The expansion of each definition is thus dependent upon the syntax definitions, module definitions, and imports that precede it in the list of definitions at the front of a body. Any definition that is intended to effect how other definitions are processed by the expander must appear before the other definitions.

Section 10.2. Keyword Bindings

This section describes forms that establish bindings between keywords and transformers. Keyword bindings may be established at top level, using define-syntax, or locally, using let-syntax, letrec-syntax, or internal define-syntax. Existing keyword bindings may be rebound temporarily with fluid-let-syntax.


syntax: (define-syntax keyword exp)
syntax: (define-syntax (keyword varexp1 exp2 ...)
returns: unspecified

In the first form, exp must evaluate to a transformer. The second form is useful only when using syntax-case to define transformers (Section 10.4) and is an abbreviation for the following.

(define-syntax keyword (lambda (varexp1 exp2 ...))

The example below defines let* as a syntactic extension, specifying the transformer with syntax-rules (see Section 10.3).

(define-syntax let*
  (syntax-rules ()
    [(_ () e1 e2 ...) (let () e1 e2 ...)]
    [(_ ([i1 v1] [i2 v2] ...) e1 e2 ...)
     (let ([i1 v1])
       (let* ([i2 v2] ...) e1 e2 ...))]))

define-syntax forms appearing at top level behave similarly to top-level variable definitions, and define-syntax forms appearing at the front of a lambda or other body behave similarly to internal variable definitions. That is, a binding established by a top-level define-syntax form is visible globally, whereas one established by an internal define-syntax form is visible only within the body in which the define-syntax form appears.

All bindings established by a set of internal definitions, whether keyword or variable definitions, are visible within the definitions themselves. For example, the expression

(let ()
  (define even?
    (lambda (x)
      (or (= x 0) (odd? (- x 1)))))
  (define-syntax odd?
    (syntax-rules ()
      [(_ x) (not (even? x))]))
  (even? 10))

is valid and should return #t.

An implication of the left-to-right processing order is that one internal definition can affect whether a subsequent form is also a definition. For example, the expression

(let ()
  (define-syntax bind-to-zero
    (syntax-rules ()
      [(_ id) (define id 0)]))
  (bind-to-zero x)
  x)

evaluates to 0, regardless of any binding for bind-to-zero that might appear outside of the let expression.

A top-level syntactic definition must be established before its first use in order for that use to be recognized.


syntax: (let-syntax ((keyword exp) ...) form1 form2 ...)
syntax: (letrec-syntax ((keyword exp) ...) form1 form2 ...)
returns: see explanation

Each exp must evaluate to a transformer. For both let-syntax and letrec-syntax, each keyword is bound within the forms form1 form2 .... For letrec-syntax the binding scope also includes each exp.

A let-syntax or letrec-syntax form may expand into one or more expressions anywhere expressions are permitted, in which case the resulting expressions are treated as if enclosed in a begin expression. This allows a let-syntax or letrec-syntax form to expand into a definition or sequence of definitions anywhere definitions are permitted, in which case the definitions are treated as if they appeared in place of the let-syntax or letrec-syntax form. (This differs from the Revised5 Report treatment of these forms; see page 207.)

The following example highlights how let-syntax and letrec-syntax differ.

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

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

The two expressions are identical except that the let-syntax form in the first expression is a letrec-syntax form in the second. In the first expression, the f occurring in g refers to the let-bound variable f, whereas in the second it refers to the keyword f whose binding is established by the letrec-syntax form.


syntax: (fluid-let-syntax ((keyword exp) ...) form1 form2 ...)
returns: see explanation

Each exp must evaluate to a transformer. fluid-let-syntax is similar to 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.

Section 10.3. Syntax-Rules Transformers

The syntax-rules form described in this section permits simple transformers to be specified in a convenient manner. These transformers may be bound to keywords using the mechanisms described in Section 10.2. While it is much less expressive than the mechanism described in Section 10.4, it is sufficient for defining many common syntactic extensions.


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

Each literal must be an identifier. Each clause must take one of the following two forms.

(pattern template)
(pattern fender template)

Each pattern specifies one possible syntax that the input form might take, and the corresponding template specifies how the output should appear in each case. The optional fender serves as an additional constraint on acceptance of a clause. Fenders are described with syntax-case in the following section.

Patterns consist of list structure, vector structure, identifiers, and constants. Each identifier within a pattern is either a literal, a pattern variable, or an ellipsis. The identifier ... is an ellipsis. Any identifier other than ... is a literal if it appears in the list of literals (literal ...); otherwise, it is a pattern variable. Literals serve as auxiliary keywords, such as else in case and cond expressions. List and vector structure within a pattern specifies the basic structure required of the input, pattern variables specify arbitrary substructure, and literals and constants specify atomic pieces that must match exactly. Ellipses specify repeated occurrences of the subpatterns they follow.

An input form F matches a pattern P if and only if

The outermost structure of a syntax-rules pattern must actually be in one of the list-structured forms above, although subpatterns of the pattern may be in any of the above forms. Furthermore, the first element of the outermost pattern is ignored, since it is always assumed to be the keyword naming the syntactic form. (These statements do not apply to syntax-case; see Section 10.4.)

If an input form passed to a syntax-rules transformer matches the pattern for a given clause, the clause is accepted and the form is transformed as specified by the associated template. As this transformation takes place, pattern variables appearing in the pattern are bound to the corresponding input subforms. Pattern variables appearing within a subpattern followed by one or more ellipses may be bound to a set or sets of zero or more input subforms.

A template is a pattern variable, an identifier that is not a pattern variable, a pattern datum, a list of subtemplates (S1 ... Sn), an improper list of subtemplates (S1 S2 ... Sn . T), or a vector of subtemplates #(S1 ... Sn). Each subtemplate Si is either a template or a template followed by one or more ellipses. The final element T of an improper subtemplate list is a template.

Pattern variables appearing within a template are replaced in the output by the input subforms to which they are bound. Pattern data and identifiers that are not pattern variables are inserted directly into the output. List and vector structure within the template remains list and vector structure in the output. A subtemplate followed by an ellipsis expands into zero or more occurrences of the subtemplate. The subtemplate must contain at least one pattern variable from a subpattern followed by an ellipsis. (Otherwise, the expander could not determine how many times the subform should be repeated in the output.) Pattern variables that occur in subpatterns followed by one or more ellipses may occur only in subtemplates that are followed by (at least) as many ellipses. These pattern variables are replaced in the output by the input subforms to which they are bound, distributed as specified. If a pattern variable is followed by more ellipses in the template than in the associated pattern, the input form is replicated as necessary.

A template of the form (... template) is identical to template, except that ellipses within the template have no special meaning. That is, any ellipses contained within template are treated as ordinary identifiers. In particular, the template (... ...) produces a single ellipsis, .... This allows syntactic extensions to expand into forms containing ellipses.

The definition of or below demonstrates the use of syntax-rules.

(define-syntax or
  (syntax-rules ()
    [(_) #f]
    [(_ e) e]
    [(_ e1 e2 e3 ...)
     (let ([t e1]) (if t t (or e2 e3 ...)))]))

The input patterns specify that the input must consist of the keyword and zero or more subexpressions. An underscore ( _ ), which is an ordinary pattern variable, is used by convention for the keyword position to remind the programmer and anyone reading the definition that the keyword position never fails to contain the expected keyword and need not be matched. (In fact, as mentioned above, syntax-rules ignores what appears in the keyword position.) If more than one subexpression is present (third clause), the expanded code both tests the value of the first subexpression and returns the value if it is not false. To avoid evaluating the expression twice, the transformer introduces a binding for the temporary variable t.

The expansion algorithm maintains lexical scoping automatically by renaming local identifiers as necessary. Thus, the binding for t introduced by the transformer is visible only within code introduced by the transformer and not within subforms of the input. Similarly, the references to the identifiers let and if are unaffected by any bindings present in the context of the input.

(let ([if #f])
  (let ([t 'okay])
    (or if t))) <graphic> okay

This expression is transformed during expansion to the equivalent of the expression below.

((lambda (if1)
   ((lambda (t1)
      ((lambda (t2)
         (if t2 t2 t1))
       if1))
    'okay))
 #f) <graphic> okay

In this sample expansion, if1, t1, and t2 represent identifiers to which if and t in the original expression and t in the expansion of or have been renamed.

The definition of a simplified version of cond below (simplified because it requires at least one output expression per clause and does not support the auxiliary keyword =>) demonstrates how auxiliary keywords such as else are recognized in the input to a transformer, via inclusion in the list of literals.

(define-syntax cond
  (syntax-rules (else)
    [(_ (else e1 e2 ...)) (begin e1 e2 ...)]
    [(_ (e0 e1 e2 ...)) (if e0 (begin e1 e2 ...))]
    [(_ (e0 e1 e2 ...) c1 c2 ...)
     (if e0 (begin e1 e2 ...) (cond c1 c2 ...))]))

Section 10.4. Syntax-Case Transformers

This section describes a more expressive mechanism for creating transformers, based on syntax-case, a generalized version of syntax-rules. This mechanism permits more complex transformations to be specified, including transformations that "bend" lexical scoping in a controlled manner, allowing a much broader class of syntactic extensions to be defined. Any transformer that may be defined using syntax-rules may be rewritten easily to use syntax-case instead; in fact, syntax-rules itself may be defined as a syntactic extension in terms of syntax-case, as demonstrated within the description of syntax below.

With this mechanism, transformers are procedures of one argument. The argument is a syntax object representing the form to be processed. The return value is a syntax object representing the output form. A syntax object contains contextual information about a form in addition to its structure. This contextual information is used by the expander to maintain lexical scoping.

A syntax object representing an identifier is itself referred to as an identifier; thus, the term identifier may refer either to the syntactic entity (symbol, variable, or keyword) or to the concrete representation of the syntactic entity as a syntax object. It is rarely necessary to distinguish the two uses.

Transformers destructure their input with syntax-case and rebuild their output with syntax. These two forms alone are sufficient for defining many syntactic extensions, including any that can be defined using syntax-rules. They are described below along with a set of additional forms and procedures that provide added functionality.


syntax: (syntax-case exp (literal ...) clause ...)
returns: see below

Each literal must be an identifier. Each clause must take one of the following two forms.

(pattern output-expression)
(pattern fender output-expression)

syntax-case patterns may be in any of the forms described in Section 10.3.

syntax-case first evaluates exp, then attempts to match the resulting value against the pattern from the first clause. This value is usually a syntax object, but it may be any Scheme object. If the value matches the pattern and no fender is present, output-expression is evaluated and its value returned as the value of the syntax-case expression. If the value does not match the pattern, the value is compared against the next clause, and so on. An error is signaled if the value does not match any of the patterns.

If the optional fender is present, it serves as an additional constraint on acceptance of a clause. If the value of the syntax-case exp matches the pattern for a given clause, the corresponding fender is evaluated. If fender evaluates to a true value, the clause is accepted; otherwise, the clause is rejected as if the input had failed to match the pattern. Fenders are logically a part of the matching process, i.e., they specify additional matching constraints beyond the basic structure of an expression.

Pattern variables contained within a clause's pattern are bound to the corresponding pieces of the input value within the clause's fender (if present) and output-expression. Pattern variables occupy the same name space as program variables and keywords; pattern variable bindings created by syntax-case can shadow (and be shadowed by) program variable and keyword bindings as well as other pattern variable bindings. Pattern variables, however, can be referenced only within syntax expressions.

See the examples following the description of syntax.


syntax: (syntax template)
syntax: #'template
returns: see below

#'template is equivalent to (syntax template). The abbreviated form is converted into the longer form by the Scheme reader (see read).

A syntax expression is like a quote expression except that the values of pattern variables appearing within template are inserted into template, and contextual information associated both with the input and with the template is retained in the output to support lexical scoping. List and vector structures within the template become true lists or vectors (suitable for direct application of list or vector operations, like map or vector-ref) to the extent that the list or vector structures must be copied to insert the values of pattern variables. A syntax template is identical to a syntax-rules template and is treated similarly.

Both definitions of or below are equivalent to the one given in Section 10.3 except that they employ syntax-case and syntax in place of syntax-rules.

(define-syntax or
  (lambda (x)
    (syntax-case x ()
      [(_) (syntax #f)]
      [(_ e) (syntax e)]
      [(_ e1 e2 e3 ...)
       (syntax (let ([t e1]) (if t t (or e2 e3 ...))))])))

(define-syntax or
  (lambda (x)
    (syntax-case x ()
      [(_) #'#f]
      [(_ e) #'e]
      [(_ e1 e2 e3 ...)
       #'(let ([t e1]) (if t t (or e2 e3 ...)))])))

In these versions, the lambda expression that produces the transformer is explicit, as are the syntax forms in the output part of each clause. The latter abbreviates the syntax forms with #'. Any syntax-rules form can be expressed with syntax-case by making the lambda expression and syntax expressions explicit. This observation leads to the following definition of syntax-rules in terms of syntax-case.

(define-syntax syntax-rules
  (lambda (x)
    (define clause
      (lambda (y)
        (syntax-case y ()
          [((keyword . pattern) template)
           #'((dummy . pattern) #'template)]
          [((keyword . pattern) fender template)
           #'((dummy . pattern) fender #'template)]
          [_ (syntax-error x)])))
    (syntax-case x ()
      [(_ (k ...) cl ...)
       (andmap identifier? #'(k ...))
       (with-syntax ([(cl ...) (map clause #'(cl ...))])
         #'(lambda (x) (syntax-case x (k ...) cl ...)))])))

The unreferenced pattern variable dummy is used in place of each keyword since the first position of each syntax-rules pattern is always ignored. The clause helper handles the optional fender. It uses syntax-error (page 229 to force the entire syntax-rules form to be identified if a syntax error is detected.

Since the lambda and syntax expressions are implicit in a syntax-rules form, definitions expressed with syntax-rules are often shorter than the equivalent definitions expressed with syntax-case. The choice of which to use when either suffices is a matter of taste, but many transformers that can be written easily with syntax-case cannot be written easily or at all with syntax-rules (see The Scheme Programming Language, Third Edition Section 8.4).


procedure: (identifier? obj)
returns: #t if obj is an identifier, #f otherwise

identifier? is often used within fenders to verify that certain subforms of an input form are identifiers, as in the definition of unnamed let below.

(define-syntax let
  (lambda (x)
    (define ids?
      (lambda (ls)
        (or (null? ls)
            (and (identifier? (car ls))
                 (ids? (cdr ls))))))
    (syntax-case x ()
      [(_ ((i v) ...) e1 e2 ...)
       (ids? #'(i ...))
       #'((lambda (i ...) e1 e2 ...) v ...)])))

Syntactic extensions ordinarily take the form (keyword subform ...), but the syntax-case system permits them to take the form of singleton identifiers as well. For example, the keyword pcar in the expression below may be used both as an identifier (in which case it expands into a call to car) or as a structured form (in which case it expands into a call to set-car!).

(let ([p (cons 0 #f)])
  (define-syntax pcar
    (lambda (x)
      (syntax-case x ()
        [_ (identifier? x) #'(car p)]
        [(_ v) #'(set-car! p v)])))
  (let ([a pcar])
    (pcar 1)
    (list a pcar))) <graphic> (0 1)

The fender (identifier? x) is used to recognize the singleton identifier case. Additional control over the expansion of singleton identifiers may be exercised with identifier-syntax, which is described below.


syntax: (identifier-syntax tmpl)
syntax: (identifier-syntax (id1 tmpl1) ((set! id2 e2tmpl2))
returns: a transformer

When a keyword is bound to a transformer produced by the first form of identifier-syntax, references to the keyword within the scope of the binding are replaced by tmpl.

(let ()
  (define-syntax a (identifier-syntax car))
  (list (a '(1 2 3)) a)) <graphic> (1 #<procedure car>)

This form of identifier-syntax may be expressed as a syntax-case transformer as follows:

(define-syntax identifier-syntax
  (lambda (x)
    (syntax-case x ()
      [(_ e)
       #'(lambda (x)
           (syntax-case x ()
             [id
              (identifier? #'id) 
              #'e]
             [(id x (... ...))
              (identifier? #'id)
              #'(e x (... ...))]))])))

With the first form of identifier-syntax, attempting to assign the associated keyword with set! fails with an "invalid syntax" message. The second, more general, form of identifier-syntax permits the transformer to determine what happens when set! is used.

(let ([x (list 0)])
  (define-syntax a
    (identifier-syntax
      (id (car x))
      ((set! id e) (set-car! x e))))
  (let ([before a])
    (set! a 1)
    (list before a x))) <graphic> (0 1 (1))

This form cannot be defined in terms of syntax-case and is thus supported as primitive by the syntax-case expander.

The second form of identifier-syntax allows a simpler definition of the method form described on page t205 in The Scheme Programming Language, Third Edition.

(define-syntax method
  (lambda (x)
    (syntax-case x ()
      [(k (ivar ...) formals e1 e2 ...)
       (with-syntax ([(index ...)
                      (let f ([i 0] [ls #'(ivar ...)])
                        (if (null? ls)
                            '()
                            (cons i (f (+ i 1) (cdr ls)))))]
                     [self (datum->syntax #'k 'self)])
         #'(lambda (self . formals)
             (let-syntax ([ivar (identifier-syntax
                                  [_ (vector-ref self index)]
                                  [(set! _ e)
                                   (vector-set! self index e)])]
                          ...)
               e1 e2 ...)))])))

This form might be used as a building block in an object-oriented subsystem. It returns a procedure that accepts an instance, self, and a set of additional arguments. The instance is assumed to be represented as a vector. Within the body of the method, e1 e2 ..., references and assignments to the instance variables ivar ... are translated into vector references and assignments to the elements of the instance. To support instance-variable assignments with only the first form of identifier-syntax, it is necessary to establish a local binding for set! that recognizes the instance variables ivar ... as auxiliary keywords (literals).


procedure: (bound-identifier=? identifier1 identifier2)
procedure: (free-identifier=? identifier1 identifier2)
procedure: (literal-identifier=? identifier1 identifier2)
returns: see below

Symbolic names alone do not distinguish identifiers unless the identifiers are to be used only as symbolic data. The predicates free-identifier=? and bound-identifier=? are used to compare identifiers according to their intended use as free references or bound identifiers in a given context.

The procedure bound-identifier=? is used to determine if two identifiers would be equivalent if they were to appear as bound identifiers in the output of a transformer. In other words, if bound-identifier=? returns true for two identifiers, a binding for one will capture references to the other within its scope. In general, two identifiers are bound-identifier=? only if both are present in the original program or both are introduced by the same transformer application (perhaps implicitly---see datum->syntax). bound-identifier=? can be used for detecting duplicate identifiers in a binding construct or for other preprocessing of a binding construct that requires detecting instances of the bound identifiers.

The procedure free-identifier=? is used to determine whether two identifiers would be equivalent if they were to appear as free identifiers in the output of a transformer. Because identifier references are lexically scoped, this means that (free-identifier=? id1 id2) is true if and only if the identifiers id1 and id2 refer to the same lexical or top-level binding. For this comparison, all variables are assumed to have top-level bindings, whether defined yet or not.

The procedure literal-identifier=? is similar to free-identifier=? except that the former equates top-level identifiers that come from different modules, even if they do not necessarily resolve to the same binding. syntax-rules employs literal-identifier=? to compare identifiers listed in the literals list against input identifiers. literal-identifier=? is intended for the comparison of auxiliary keywords such as else in cond and case, where no actual binding is involved. Literal identifiers (auxiliary keywords) appearing in syntax-case patterns (such as else in case and cond) are matched with literal-identifier=?.

Two identifiers that are free-identifier=? may not be bound-identifier=?. An identifier introduced by a transformer may refer to the same enclosing binding as an identifier not introduced by the transformer, but an introduced binding for one will not capture references to the other. On the other hand, identifiers that are bound-identifier=? are free-identifier=?, as long as the identifiers have valid bindings in the context where they are compared. Identifiers that are free-identifier=? are also literal-identifier=?, but the converse does not necessarily hold.

The following definition of unnamed let uses bound-identifier=? to detect duplicate identifiers.

(define-syntax let
  (lambda (x)
    (define ids?
      (lambda (ls)
        (or (null? ls)
            (and (identifier? (car ls))
                 (ids? (cdr ls))))))
    (define unique-ids?
      (lambda (ls)
        (or (null? ls)
            (and (let notmem? ([x (car ls)] [ls (cdr ls)])
                   (or (null? ls)
                       (and (not (bound-identifier=? x (car ls)))
                            (notmem? x (cdr ls)))))
                 (unique-ids? (cdr ls))))))
    (syntax-case x ()
      [(_ ((i v) ...) e1 e2 ...)
       (and (ids? #'(i ...))
            (unique-ids? #'(i ...)))
       #'((lambda (i ...) e1 e2 ...) v ...)])))

With the definition of let above, the expression

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

results in a syntax error, whereas

(let-syntax ([dolet (lambda (x)
                      (syntax-case x ()
                        [(_ b)
                         #'(let ([a 3] [b 4]) (+ a b))]))])
  (dolet a))

evaluates to 7 since the identifier a introduced by dolet and the identifier a extracted from the input form are not bound-identifier=?. Since both occurrences of a, however, if left as free references, would refer to the same (top-level) binding for a, neither free-identifier=? nor literal-identifier=? would distinguish them.

The two definitions of a simplified version of cond below are equivalent; the first includes else in the literals list for syntax-case, whereas the second explicitly tests for else using literal-identifier=?.

(define-syntax cond
  (lambda (x)
    (syntax-case x (else)
      [(_ (else e1 e2 ...)) #'(begin e1 e2 ...)]
      [(_ (e0 e1 e2 ...)) #'(if e0 (begin e1 e2 ...))]
      [(_ (e0 e1 e2 ...) c1 c2 ...)
       #'(if e0 (begin e1 e2 ...) (cond c1 c2 ...))])))

(define-syntax cond
  (lambda (x)
    (syntax-case x ()
      [(_ (e0 e1 e2 ...))
       (and (identifier? #'e0)
            (literal-identifier=? #'e0 #'else))
       #'(begin e1 e2 ...)]
      [(_ (e0 e1 e2 ...)) #'(if e0 (begin e1 e2 ...))]
      [(_ (e0 e1 e2 ...) c1 c2 ...)
       #'(if e0 (begin e1 e2 ...) (cond c1 c2 ...))])))

With either definition of cond, else is not recognized as an auxiliary keyword if an enclosing lexical binding for else exists. For example,

(let ([else #f])
  (cond [else (write "oops")]))

does not write "oops", since else is bound lexically and is therefore not the same else that appears in the definition of cond.


syntax: (with-syntax ((pattern val) ...) exp1 exp2 ...)
returns: the value of the last expi

It is sometimes useful to construct a transformer's output in separate pieces, then put the pieces together. with-syntax facilitates this by allowing the creation of local pattern bindings.

pattern is identical in form to a syntax-case pattern. The value of each val is computed and destructured according to the corresponding pattern, and pattern variables within the pattern are bound as with syntax-case to appropriate portions of the value within exp1 exp2 ....

with-syntax may be defined as a syntactic extension in terms of syntax-case.

(define-syntax with-syntax
  (lambda (x)
    (syntax-case x ()
      [(_ ((p e0) ...) e1 e2 ...)
       #'(syntax-case (list e0 ...) ()
           [(p ...) (begin e1 e2 ...)])])))

The following definitions of full cond and case demonstrate the use of with-syntax to support transformers that employ recursion internally to construct their output.

(define-syntax cond
  (lambda (x)
    (syntax-case x ()
      [(_ c1 c2 ...)
       (let f ([c1 #'c1] [cmore #'(c2 ...)])
         (if (null? cmore)
             (syntax-case c1 (else =>)
               [(else e1 e2 ...) #'(begin e1 e2 ...)]
               [(e0) #'(let ([t e0]) (if t t))]
               [(e0 => e1) #'(let ([t e0]) (if t (e1 t)))]
               [(e0 e1 e2 ...) #'(if e0 (begin e1 e2 ...))])
             (with-syntax ([rest (f (car cmore) (cdr cmore))])
               (syntax-case c1 (=>)
                 [(e0) #'(let ([t e0]) (if t t rest))]
                 [(e0 => e1) #'(let ([t e0]) (if t (e1 t) rest))]
                 [(e0 e1 e2 ...)
                  #'(if e0 (begin e1 e2 ...) rest)]))))])))

(define-syntax case
  (lambda (x)
    (syntax-case x ()
      [(_ e c1 c2 ...)
       (with-syntax
         ([body
           (let f ([c1 #'c1] [cmore #'(c2 ...)])
             (if (null? cmore)
                 (syntax-case c1 (else)
                   [(else e1 e2 ...) #'(begin e1 e2 ...)]
                   [((k ...) e1 e2 ...)
                    #'(if (memv t '(k ...)) (begin e1 e2 ...))])
                 (with-syntax ([rest
                                (f (car cmore) (cdr cmore))])
                   (syntax-case c1 ()
                     [((k ...) e1 e2 ...)
                      #'(if (memv t '(k ...))
                            (begin e1 e2 ...)
                            rest)]))))])
         #'(let ([t e]) body))])))


syntax: (quasisyntax template ...)
syntax: #`template
syntax: (unsyntax template ...)
syntax: #,template
syntax: (unsyntax-splicing template ...)
syntax: #,@template
returns: see explanation

The abbreviation #`template is equivalent to (quasisyntax template), while #,template equivalent to (unsyntax template), and #,@template to (unsyntax-splicing template). The abbreviated forms are converted into the longer forms by the Scheme reader (see read).

quasisyntax is similar to syntax, but it allows parts of the quoted text to be evaluated, in a manner similar to the operation of quasiquote (Section 6.1).

Within a quasisyntax template, subforms of unsyntax and unsyntax-splicing forms are evaluated, and everything else is treated as ordinary template material, as with syntax. The value of each unsyntax subform is inserted into the output in place of the unsyntax form, while the value of each unsyntax-splicing subform is spliced into the surrounding list or vector structure. unsyntax and unsyntax-splicing are valid only within quasisyntax expressions.

quasisyntax expressions may be nested, with each quasisyntax introducing a new level of syntax quotation and each unsyntax or unsyntax-splicing taking away a level of quotation. An expression nested within n quasisyntax expressions must be within n unsyntax or unsyntax-splicing expressions to be evaluated.

quasisyntax can be used in place of with-syntax in many cases. For example, the definintion of case shown under the description of with-syntax above can be rewritten using quasisyntax as follows.

(define-syntax case
  (lambda (x)
    (syntax-case x ()
      [(_ e c1 c2 ...)
       #`(let ([t e])
           #,(let f ([c1 #'c1] [cmore #'(c2 ...)])
               (if (null? cmore)
                   (syntax-case c1 (else)
                     [(else e1 e2 ...) #'(begin e1 e2 ...)]
                     [((k ...) e1 e2 ...)
                      #'(if (memv t '(k ...)) (begin e1 e2 ...))])
                   (syntax-case c1 ()
                     [((k ...) e1 e2 ...)
                      #`(if (memv t '(k ...))
                            (begin e1 e2 ...)
                            #,(f (car cmore) (cdr cmore)))]))))])))

unsyntax and unsyntax-splicing forms that contain zero or more than one subform are valid only in splicing (list or vector) contexts. (unsyntax template ...) is equivalent to (unsyntax template) ..., and (unsyntax-splicing template ...) is equivalent to (unsyntax-splicing template) .... These forms are primarily useful as intermediate forms in the output of the quasisyntax expander. They support certain useful nested quasiquotation (quasisyntax) idioms [2], such as #,@#,@, which has the effect of a doubly indirect splicing when used within a doubly nested and doubly evaluated quasisyntax expression, as with the nested quasiquote examples shown in Section 6.1.


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

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>)


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

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>)


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

The procedure syntax->datum strips all syntactic information from a syntax object and returns the corresponding Scheme "datum."

syntax->datum and syntax-object->datum are identical. The former is the Revised6 Report name.

Identifiers stripped in this manner are converted to their symbolic names, which can then be compared with eq?. Thus, a predicate symbolic-identifier=? might be defined as follows.

(define symbolic-identifier=?
  (lambda (x y)
    (eq? (syntax->datum x)
         (syntax->datum y))))

Two identifiers that are free-identifier=? are symbolic-identifier=?; in order to refer to the same binding, two identifiers must have the same name. The converse is not always true, since two identifiers may have the same name but different bindings.


syntax: (datum template)
returns: see below

(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 (syntax t))]))

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


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

datum->syntax constructs a syntax object from obj that contains the same contextual information as template-identifier, with the effect that the syntax object behaves as if it were introduced into the code when template-identifier was introduced. The template identifier is often the keyword of an input form, extracted from the form, and the object is often a symbol naming an identifier to be constructed.

datum->syntax and datum->syntax-object are identical. The former is the Revised6 Report name.

datum->syntax allows a transformer to "bend" lexical scoping rules by creating implicit identifiers that behave as if they were present in the input form, thus permitting the definition of syntactic extensions that introduce visible bindings for or references to identifiers that do not appear explicitly in the input form. For example, we can define a loop expression that binds the variable break to an escape procedure within the loop body.

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

With this definition, the expression

(let ([n 3] [ls '()] [f cons])
  (loop
    (if (= n 0) (break ls))
    (set! ls (f 'a ls))
    (set! n (- n 1))))

expands to the equivalent of

(let ([n1 3] [ls1 '()] [f1 cons])
  (call-with-current-continuation
    (lambda (break1)
      (let f2 ()
        (if (= n1 0) (break1 ls1))
        (set! ls1 (f1 'a ls1))
        (set! n1 (- n1 1))
        (f2)))))

and evaluates to (a a a). In the expansion, the variables whose bindings appear in the source expression, n, ls, and f, have been renamed n1, ls1, and f1. The other f, whose binding is inserted during the expansion of the loop form, has been renamed f2. The variable break, whose binding is also inserted during the expansion of the loop form, is renamed break1 to signify that it is treated as if present in the source expression. Were we to define loop instead as

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

the variable break would not be visible in e .... The expression given above would expand to the equivalent of

(let ([n1 3] [ls1 '()] [f1 cons])
  (call-with-current-continuation
    (lambda (break2)
      (let f2 ()
        (if (= n1 0) (break ls1))
        (set! ls1 (f1 'a ls1))
        (set! n1 (- n1 1))
        (f2)))))

in which the reference to break does not resolve to the introduced binding for break; in fact, since no other binding for break is evident, it is not renamed, and break will refer to the top-level (primitive) break.

It is also useful for obj to represent an arbitrary Scheme form, as demonstrated by the definition of include given within the description of include below.


syntax: (with-implicit (id0 id1 ...) e1 e2 ...)
returns: see below

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

(with-implicit (id0 id1 ...)
  e1 e2 ...)

is equivalent to

(with-syntax ([id1 (datum->syntax #'id0 'id1)] ...)
  e1 e2 ...)

with-implicit can be defined simply as follows.

(define-syntax with-implicit
  (syntax-rules ()
    [(_ (tid id ...) e1 e2 ...)
     (with-syntax ([id (datum->syntax (syntax tid) 'id)] ...)
       e1 e2 ...)]))

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 filename)
returns: unspecified

include expands into a begin expression containing the forms found in the file named by filename. 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 filename 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 11.4) determines the set of directories searched for source files not identified by absolute path names.


procedure: (generate-temporaries list)
returns: a list of distinct generated identifiers

Transformers can introduce a fixed number of identifiers into their output by naming each identifier. In some cases, however, the number of identifiers to be introduced depends upon some characteristic of the input expression. A straightforward definition of letrec, for example, requires as many temporary identifiers as there are binding pairs in the input expression. The procedure generate-temporaries is used to construct lists of temporary identifiers.

list may be any list; its contents are not important. The number of temporaries generated is the number of elements in list. Each temporary is guaranteed to be different from all other identifiers.

A definition of letrec that uses generate-temporaries is shown below.

(define-syntax letrec
  (lambda (x)
    (syntax-case x ()
      [(_ ((i v) ...) e1 e2 ...)
       (with-syntax ([(t ...) (generate-temporaries #'(i ...))])
         #'(let ([i #f] ...)
             (let ([t v] ...)
               (set! i t) ...
               (let () e1 e2 ...))))])))

Any transformer that uses generate-temporaries in this fashion can be rewritten to avoid using it, albeit with a loss of clarity. The trick is to use a recursively defined intermediate form that generates one temporary per expansion step and completes the expansion after enough temporaries have been generated. Here is a definition of let-values (see page 83) that uses this technique to support multiple sets of bindings.

(define-syntax let-values
  (syntax-rules ()
    [(_ () f1 f2 ...) (let () f1 f2 ...)]
    [(_ ((fmls1 expr1) (fmls2 expr2) ...) f1 f2 ...)
     (lvhelp fmls1 () () expr1
       ((fmls2 expr2) ...) (f1 f2 ...))]))

(define-syntax lvhelp
  (syntax-rules ()
    [(_ (x1 . fmls) (x ...) (t ...) e m b)
     (lvhelp fmls (x ... x1) (t ... tmp) e m b)]
    [(_ () (x ...) (t ...) e m b)
     (call-with-values
       (lambda () e)
       (lambda (t ...)
         (let-values m (let ([x t] ...) . b))))]
    [(_ xr (x ...) (t ...) e m b)
     (call-with-values
       (lambda () e)
       (lambda (t ... . tmpr)
         (let-values m (let ([x t] ... [xr tmpr]) . b))))]))

The implementation of lvhelp is complicated by the need to evaluate all of the right-hand-side expressions before creating any of the bindings and by the need to support improper formals lists.

A definition of letrec that does not use generate-temporaries is left as an exercise for the reader.


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

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 definition of let on page 220 by rewriting the definition as shown below.

(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 v) ...) e1 e2 ...)
       (begin
         (check-ids! #'(i ...))
         (check-unique! #'(i ...))
         #'((lambda (i ...) e1 e2 ...) v ...))])))

With this change, the expression

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

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

Section 10.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" [26], which describes modules and their implementation in more detail.


syntax: (module name interface defn ... init ...)
syntax: (module interface defn ... init ...)
syntax: (import import-spec)
syntax: (import-only import-spec)
returns: unspecified

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 ...). Each import-spec must take one of the following forms.

<import-spec><graphic><id>
|(only <import-spec> <id>*)
|(except <import-spec> <id>*)
|(add-prefix <import-spec> <id>)
|(drop-prefix <import-spec> <id>)
|(rename <import-spec> (<new-id> <old-id>)*)
|(alias <import-spec> (<new-id> <old-id>)*)

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 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. Each identifier listed in a module's interface must be defined within that module. Because module and import are definitions, they may appear at the top level of a program, nested within the bodies of lambda expressions, and nested within other modules. Also, because module names are scoped like other identifiers, modules 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 implicit imports that are visible only within the expansion of syntactic abstractions exported from the module. This form is thus useful only when identifier is a keyword naming a syntactic abstraction. In the current implementation, implicit imports need be listed only when identifier is exported by a top-level module, although implicit imports may be listed in other contexts as well. Implicit exports are listed so that the compiler can determine the exact set of bindings (explicit and implicit) that must be inserted into the top-level environment, and conversely, the set of bindings that may be treated more efficiently as local bindings.

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.

An import or import-only form makes the specified bindings visible. They differ in that import leaves all bindings except for those shadowed by the imported names visible, whereas import-only hides all existing bindings, i.e., makes only the imported names visible, when used in a local scope. (It behaves like plain import at top level.) Each import-spec identifies a set of names to make visible as follows.

name:
all exports of module name

(only import-spec id ...):
of those specified by import-spec, just id ...

(except import-spec id ...):
all specified by import-spec except id ...

(add-prefix import-spec id):
all specified by import-spec, each prefixed by id

(drop-prefix import-spec id):
all specified by import-spec, with prefix id removed

(rename import-spec (new-id old-id) ...):
all specified by import-spec, with each old-id renamed to the corresponding new-id

(alias import-spec (new-id old-id) ...):
all specified by import-spec, with each new-id as an alias for old-id

An error is signaled if the given selection or transformation cannot be made because of a missing export or prefix.

Identifiers exported from a module are visible within the module and where the module is imported. An identifier made visible via an import of a module is scoped as if its definition appears where the import occurs. The following example illustrates these scoping rules.

(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

The inner let expression binds y to the value of the x bound by the outer let. The import of m makes the definitions of x and setter visible within the inner let. In the expression (+ x y z), x refers to the identifier macro exported from m while y and z refer to the bindings established by the inner let. The identifier macro x expands into a reference to the variable z defined within the 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, import-only 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, it is necessary 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, 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 module program given above 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 lambda 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.

It is often convenient to refer to one export of a module without importing all of its exports. This can be accomplished via the extended import specifier only.

(module m (x y z)
  (define x 1)
  (define y 2)
  (define z 3))

(let ([x 11] [y 12] [z 13])
  (import (only m y))
  (list x y z)) <graphic> (11 2 13)

With local import forms, it is rarely necessary to use the extended import specifiers. For example, an abstraction that encapsulates the import and reference can easily be defined and used as follows.

(define-syntax from
  (syntax-rules ()
    [(_ m id) (let () (import-only m) id)]))

(let ([x 10])
  (module m1 (x) (define x 1))
  (module m2 (x) (define x 2))
  (+ (from m1 x) (from m2 x))) <graphic> 3

The definition of from could use import rather than import-only, but by using import-only we get feedback if an attempt is made to import an identifier from a module that does not export the identifier. With import instead of import-only, the current binding is used if the module does not export the specified name.

(define-syntax lax-from
  (syntax-rules ()
    [(_ m id) (let () (import m) id)]))

(let ([x 10])
  (module m1 (x) (define x 1))
  (module m2 (x) (define x 2))
  (+ (from m1 x) (from m2 y))) <graphic> error: y is not visible
 
(let ([x 10] [y 20])
  (module m1 (x) (define x 1))
  (module m2 (x) (define x 2))
  (+ (lax-from m1 x) (lax-from m2 y))) <graphic> 21

Import visibility interacts with hygienic macro expansion in such a way that, as one might expect, an identifier x imported from a module m is treated in the importing context as if the corresponding export identifier had been present in the import form along with m.

The from abstraction above works because both m and id appear in the input to the abstraction, so the imported id captures the reference to id.

The following variant of from also works, because both names are introduced into the output by the transformer.

(module m (x) (define x 'x-of-m))
(define-syntax x-from-m
  (syntax-rules ()
    [(_) (let () (import m) x)]))

(let ([x 'local-x]) (x-from-m)) <graphic> x-of-m

On the other hand, imports of introduced module names do not capture free references.

(let ([x 'local-x])
  (define-syntax alpha
    (syntax-rules ()
      [(_ var) (let () (import m) (list x var))]))
 
  (alpha x)) <graphic> (x-of-m local-x)

Similarly, imports from free module names do not capture references to introduced variables.

(let ([x 'local-x])
  (define-syntax beta
    (syntax-rules ()
      [(_ m var) (let () (import m) (list x var))]))

  (beta m x)) <graphic> (local-x x-of-m)

This semantics extends to prefixed, renamed, and aliased bindings created by the extended import specifiers add-prefix, rename, and alias.

The from abstraction works for variables but not for exported keywords or module names, since the output is an expression and may thus appear only where expressions may appear. A generalization of this technique is used in the following definition of import*, which supports renaming of imported bindings and selective import of specific bindings.

(define-syntax import*
  (syntax-rules ()
    [(_ m) (begin)]
    [(_ m (new old))
     (module (new)
       (module (tmp)
         (import m)
         (alias tmp old))
       (alias new tmp))]
    [(_ m id) (module (id) (import m))]
    [(_ m spec0 spec1 ...)
     (begin (import* m spec0) (import* m spec1 ...))]))

To selectively import an identifier from module m, the import* form expands into an anonymous module that first imports all exports of m then re-exports only the selected identifier. To rename on import the macro expands into an anonymous module that instead exports an alias (Section 10.9) bound to the new name.

If the output placed the definition of new in the same scope as the import of m, a naming conflict would arise whenever new is also present in the interface of m. To prevent this, the output instead places the import within a nested anonymous module and links old and new by means of an alias for the introduced identifier tmp.

The macro expands recursively to handle multiple import specifications. The following imports cons as + and + as cons, which is probably not a very good idea.

(let ()
  (import* scheme (+ cons) (cons +))
  (+ (cons 1 2) (cons 3 4))) <graphic> (3 . 7)

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)
           (error '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

Section 10.6. 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

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


module: r5rs

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

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

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

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

Section 10.7. Meta Definitions


syntax: (meta . definition)
returns: unspecified

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 ---) ---)))

As with define-syntax rhs expressions, meta expressions can evaluate references only to identifiers whose values are (already) available in the compile-time environment, e.g., macros and meta variables. They can, however, like define-syntax rhs expressions, build syntax objects containing occurrences of any identifiers in their scope.

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 "filename")

to create groups of meta bindings.

Section 10.8. Conditional expansion

Expansion-time decisions can be made via meta-cond, which is similar to cond but evaluates the test expressions at expansion time.


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

Each clause but the last must take the form:

(test exp1 exp2 ...)

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

(else exp1 exp2 ...)

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 exp1 exp2 .... 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 exp1 exp2 ... 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 10.9. Aliases


syntax: (alias id1 id2)
returns: unspecified

alias is used to create an alias 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

Aliases appearing at top level track the current binding for the aliased identifier.

(alias foo lambda)
(define lambda 3)
foo <graphic> 3

R. Kent Dybvig / Chez Scheme Version 7 User's Guide
Copyright © 2005 R. Kent Dybvig
Revised July 2007 for Chez Scheme Version 7.4
Cadence Research Systems / www.scheme.com
Cover illustration © 1998 Jean-Pierre Hébert
ISBN: 0-9667139-1-5
to order this book / about this book