doc work
svn: r6692
This commit is contained in:
parent
516146bb5c
commit
2fe7c75dc1
|
@ -154,7 +154,7 @@
|
|||
(provide defproc defproc* defstruct defthing defform defform* defform/subs defform*/subs defform/none
|
||||
specform specform/subs
|
||||
specsubform specspecsubform specsubform/inline
|
||||
schemegrammar
|
||||
schemegrammar schemegrammar*
|
||||
var svar void-const undefined-const)
|
||||
|
||||
(define void-const
|
||||
|
@ -295,8 +295,16 @@
|
|||
(syntax-rules ()
|
||||
[(_ #:literals (lit ...) id clause ...) (*schemegrammar '(lit ...)
|
||||
'(id clause ...)
|
||||
(lambda () (list (scheme id) (schemeblock0 clause) ...)))]
|
||||
(lambda () (list (list (scheme id) (schemeblock0 clause) ...))))]
|
||||
[(_ id clause ...) (schemegrammar #:literals () id clause ...)]))
|
||||
(define-syntax schemegrammar*
|
||||
(syntax-rules ()
|
||||
[(_ #:literals (lit ...) [id clause ...] ...) (*schemegrammar '(lit ...)
|
||||
'(id ... clause ... ...)
|
||||
(lambda ()
|
||||
(list
|
||||
(list (scheme id) (schemeblock0 clause) ...) ...)))]
|
||||
[(_ [id clause ...] ...) (schemegrammar #:literals () [id clause ...] ...)]))
|
||||
(define-syntax var
|
||||
(syntax-rules ()
|
||||
[(_ id) (*var 'id)]))
|
||||
|
@ -589,27 +597,34 @@
|
|||
sub-procs))))
|
||||
(flow-paragraphs (decode-flow (content-thunk)))))))
|
||||
|
||||
(define (*schemerawgrammar nonterm clause1 . clauses)
|
||||
(define (*schemerawgrammars nonterms clauseses)
|
||||
(make-table
|
||||
'((valignment baseline baseline baseline baseline baseline)
|
||||
(alignment left left center left left))
|
||||
(alignment right left center left left))
|
||||
(let ([empty-line (make-flow (list (make-paragraph (list (tt 'nbsp)))))]
|
||||
[to-flow (lambda (i) (make-flow (list (make-paragraph (list i)))))])
|
||||
(cons
|
||||
(list (to-flow nonterm)
|
||||
empty-line
|
||||
(to-flow "=")
|
||||
empty-line
|
||||
(make-flow (list clause1)))
|
||||
(map (lambda (clause)
|
||||
(list empty-line
|
||||
empty-line
|
||||
(to-flow "|")
|
||||
empty-line
|
||||
(make-flow (list clause))))
|
||||
clauses)))))
|
||||
(apply append
|
||||
(map
|
||||
(lambda (nonterm clauses)
|
||||
(cons
|
||||
(list (to-flow nonterm)
|
||||
empty-line
|
||||
(to-flow "=")
|
||||
empty-line
|
||||
(make-flow (list (car clauses))))
|
||||
(map (lambda (clause)
|
||||
(list empty-line
|
||||
empty-line
|
||||
(to-flow "|")
|
||||
empty-line
|
||||
(make-flow (list clause))))
|
||||
(cdr clauses))))
|
||||
nonterms clauseses)))))
|
||||
|
||||
(define (*schemegrammar lits s-expr clauses-thunk)
|
||||
(define (*schemerawgrammar nonterm clause1 . clauses)
|
||||
(*schemerawgrammars (list nonterm) (list (cons clause1 clauses))))
|
||||
|
||||
(define (*schemegrammar lits s-expr clauseses-thunk)
|
||||
(parameterize ([current-variable-list
|
||||
(let loop ([form s-expr])
|
||||
(cond
|
||||
|
@ -619,7 +634,8 @@
|
|||
[(pair? form) (append (loop (car form))
|
||||
(loop (cdr form)))]
|
||||
[else null]))])
|
||||
(apply *schemerawgrammar (clauses-thunk))))
|
||||
(let ([l (clauseses-thunk)])
|
||||
(*schemerawgrammars (map car l) (map cdr l)))))
|
||||
|
||||
(define (*var id)
|
||||
(to-element (*var-sym id)))
|
||||
|
|
|
@ -13,7 +13,7 @@ nevertheless implemented as structures, and we defer discussion of
|
|||
objects to @secref["classes"].
|
||||
|
||||
@; ------------------------------------------------------------
|
||||
@section{Simple Structure Types}
|
||||
@section{Simple Structure Types: @scheme[define-struct]}
|
||||
|
||||
To a first approximation, the syntax of @scheme[define-struct] is
|
||||
|
||||
|
|
|
@ -87,6 +87,4 @@ form, a @scheme[_thing] is either an identifier or a keyword.
|
|||
@include-section["cond.scrbl"]
|
||||
@include-section["begin.scrbl"]
|
||||
@include-section["set.scrbl"]
|
||||
|
||||
@section{Quoted Data: @scheme[quote] and @scheme[quasiquote]}
|
||||
|
||||
@include-section["quote.scrbl"]
|
||||
|
|
|
@ -37,10 +37,6 @@ In the reference manual, the documentation for each procedure
|
|||
describes the acceptable arguments and the result of the procedure
|
||||
using @idefterm{contracts}.
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@include-section["for.scrbl"]
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "classes"]{Classes and Objects}
|
||||
|
||||
|
@ -50,15 +46,11 @@ using @idefterm{contracts}.
|
|||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "threads"]{Threads}
|
||||
@include-section["for.scrbl"]
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "guide:i/o"]{Input and Output}
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "guide:networking"]{Networking}
|
||||
@include-section["io.scrbl"]
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
|
@ -68,11 +60,22 @@ using @idefterm{contracts}.
|
|||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "match"]{Pattern Matching}
|
||||
|
||||
@subsection{Simple Dispatch: @scheme[case]}
|
||||
|
||||
The @scheme[case] form dispatches to a clause by matching the result
|
||||
of an expression to the values for the clause:
|
||||
|
||||
@specform[(case [(_datum ...+) expr ...+]
|
||||
...)]
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "units"]{Units (Higher-Order Modules)}
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "threads"]{Threads}
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "guide:macros"]{Syntactic Extension@aux-elem{ (Modules and Macros)}}
|
||||
|
||||
|
@ -84,7 +87,6 @@ using @idefterm{contracts}.
|
|||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "macros"]{Reader Extension}
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "security"]{Security}
|
||||
|
||||
|
|
14
collects/scribblings/guide/io.scrbl
Normal file
14
collects/scribblings/guide/io.scrbl
Normal file
|
@ -0,0 +1,14 @@
|
|||
#reader(lib "docreader.ss" "scribble")
|
||||
@require[(lib "manual.ss" "scribble")]
|
||||
@require[(lib "eval.ss" "scribble")]
|
||||
@require["guide-utils.ss"]
|
||||
|
||||
@title[#:tag "guide:i/o"]{Input and Output}
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@section[#:tag "guide:networking"]{Networking}
|
||||
|
||||
|
||||
@; ----------------------------------------------------------------------
|
||||
@include-section["qq.scrbl"]
|
||||
|
|
@ -157,7 +157,7 @@ an @scheme[_id] is referenced before its value is ready, the result is
|
|||
@include-section["named-let.scrbl"]
|
||||
|
||||
@; ----------------------------------------
|
||||
@section{Multiple Values: @scheme[let-values], @scheme[let*-values], and @scheme[letrec-values]}
|
||||
@section{Multiple Values: @scheme[let-values], @scheme[let*-values], @scheme[letrec-values]}
|
||||
|
||||
In the same way that @scheme[define-values] binds multiple
|
||||
results in a definition (see @secref["guide:multiple-values"]),
|
||||
|
|
46
collects/scribblings/guide/qq.scrbl
Normal file
46
collects/scribblings/guide/qq.scrbl
Normal file
|
@ -0,0 +1,46 @@
|
|||
#reader(lib "docreader.ss" "scribble")
|
||||
@require[(lib "manual.ss" "scribble")]
|
||||
@require[(lib "eval.ss" "scribble")]
|
||||
@require["guide-utils.ss"]
|
||||
|
||||
@title{Quasiquoting}
|
||||
|
||||
[Explain why...]
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Escapes: @scheme[quasiquote], @scheme[unquote], and @scheme[unquote-splicing]}
|
||||
|
||||
The @scheme[quasiquote] form is similar to @scheme[quote]:
|
||||
|
||||
@specform[(#,(schemekeywordfont "quasiquote") datum)]
|
||||
|
||||
However, for each @scheme[(#,(schemekeywordfont "unquote") _expr)]
|
||||
that appears within the @scheme[_datum], the @scheme[_expr] is
|
||||
evaluated to produce a value that takes the place of the
|
||||
@scheme[unsyntax] sub-form.
|
||||
|
||||
@examples[
|
||||
(eval:alts (#,(schemekeywordfont "quasiquote") (1 2 (#,(schemekeywordfont "unquote") (+ 1 2)) (#,(schemekeywordfont "unquote") (- 5 1))))
|
||||
`(1 2 ,(+ 1 2), (- 5 1)))
|
||||
]
|
||||
|
||||
The @scheme[unquote-splicing] form is similar to @scheme[unquote], but
|
||||
its @scheme[_expr] must produce a list, and the
|
||||
@scheme[unquote-splicing] form must appear in a context that produces
|
||||
either a list of vector. As the name suggests, the resulting list
|
||||
spliced into the context of its use.
|
||||
|
||||
@examples[
|
||||
(eval:alts (#,(schemekeywordfont "quasiquote") (1 2 (#,(schemekeywordfont "unquote-splicing") (list (+ 1 2) (- 5 1))) 5))
|
||||
`(1 2 ,@(list (+ 1 2) (- 5 1)) 5))
|
||||
]
|
||||
|
||||
If a @scheme[quasiquote] form appears within an enclosing
|
||||
@scheme[quasiquote] form, then the inner @scheme[quasiquote]
|
||||
effectively cancels one layer of @scheme[unquote] and
|
||||
@scheme[unquote-splicing] forms, so that a second @scheme[unquote]
|
||||
or @scheme[unquote-splicing] is needed.
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Abbreviating with @schememetafont{`}, @schememetafont{,}, and @schememetafont[",@"]}
|
||||
|
65
collects/scribblings/guide/quote.scrbl
Normal file
65
collects/scribblings/guide/quote.scrbl
Normal file
|
@ -0,0 +1,65 @@
|
|||
#reader(lib "docreader.ss" "scribble")
|
||||
@require[(lib "manual.ss" "scribble")]
|
||||
@require[(lib "eval.ss" "scribble")]
|
||||
@require["guide-utils.ss"]
|
||||
|
||||
@title{Quoting: @scheme[quote] and @schemevalfont{'}}
|
||||
|
||||
The @scheme[quote] form produces a constant:
|
||||
|
||||
@specform[(#,(schemekeywordfont "quote") datum)]
|
||||
|
||||
The syntax of a @scheme[datum] is technically specified as anything
|
||||
that the @scheme[read] function parses as a single element. The value
|
||||
of the @scheme[quote] form is the same value that @scheme[read] would
|
||||
produce given @scheme[_datum].
|
||||
|
||||
To a good approximation, the resulting value is such that
|
||||
@scheme[_datum] is the value's printed representation. Thus, it can be
|
||||
a symbol, a boolean, a number, a (character or byte) string, a
|
||||
character, a keyword, an empty list, a pair (or list) containing more
|
||||
such values, a vector containing more such values, a hash table
|
||||
containing more such values, or a box containing another such value.
|
||||
|
||||
@examples[
|
||||
(eval:alts (#,(schemekeywordfont "quote") apple) 'apple)
|
||||
(eval:alts (#,(schemekeywordfont "quote") #t) #t)
|
||||
(eval:alts (#,(schemekeywordfont "quote") 42) 42)
|
||||
(eval:alts (#,(schemekeywordfont "quote") "hello") "hello")
|
||||
(eval:alts (#,(schemekeywordfont "quote") ()) '())
|
||||
(eval:alts (#,(schemekeywordfont "quote") ((1 2 3) #2("z" x) . the-end)) '((1 2 3) #2("z" x) . the-end))
|
||||
(eval:alts (#,(schemekeywordfont "quote") (1 2 #,(schemeparenfont ".") (3))) '(1 2 . (3)))
|
||||
]
|
||||
|
||||
As the last example above shows, the @scheme[_datum] does not have to
|
||||
be the normalized printed form of a value. For example, A
|
||||
@scheme[_datum] cannot be a printed representation that starts with
|
||||
@litchar{#<}, however, so it cannot be @|void-const|,
|
||||
@|undefined-const|, or a procedure.
|
||||
|
||||
The @scheme[quote] form is rarely used for a @scheme[_datum] that is a
|
||||
boolean, number, or string by itself, since the printed forms of those
|
||||
values can already be used as constants. The @scheme[quote] form is
|
||||
more typically used for symbols and lists, which have other meanings
|
||||
(identifiers, function calls, etc.) when not quoted.
|
||||
|
||||
An expression
|
||||
|
||||
@specform[(quote #,(scheme _datum))]
|
||||
|
||||
is a shorthand for
|
||||
|
||||
@schemeblock[
|
||||
(#,(schemekeywordfont "quote") #,(scheme _datum))
|
||||
]
|
||||
|
||||
and this shorthand is almost always used instead of
|
||||
@scheme[quote]. The shorthand applies even within the @scheme[_datum],
|
||||
so it can produce a list containing @scheme[quote].
|
||||
|
||||
@examples[
|
||||
'apple
|
||||
'"hello"
|
||||
'(1 2 3)
|
||||
(display '(you can 'me))
|
||||
]
|
|
@ -164,5 +164,5 @@ they're fundamental limitations of the traditional top-level
|
|||
environment, which Scheme and Lisp implementations have historically
|
||||
fought with ad hoc command-line flags, compiler directives, and
|
||||
build tools. The module system is to designed to avoid the problems,
|
||||
so start with @schemefont{#module}, and you'll be happier with Scheme
|
||||
in the long run.
|
||||
so start with @schemefont{#module}, and you'll be happier with
|
||||
PLT Scheme in the long run.
|
||||
|
|
|
@ -3,47 +3,48 @@
|
|||
|
||||
@title[#:tag "mz:expansion"]{Syntax Expansion}
|
||||
|
||||
Expansion recursively processes a syntax-wrapped datum to parse it. In
|
||||
Expansion recursively processes a syntax object to parse it. In
|
||||
general, the parsing of a datum depends on its outermost shape:
|
||||
|
||||
@itemize{
|
||||
|
||||
@item{If it is a (syntax-wrapped) symbol, also known as an
|
||||
@item{If it is a syntax-object symbol, also known as an
|
||||
@defterm{identifier}, then a binding is determined using symbol
|
||||
along with the lexical information in the symbol's syntax
|
||||
wrapper. The binding determines the next parsing step.}
|
||||
along with the lexical information in the identifier. The
|
||||
binding determines the next parsing step.}
|
||||
|
||||
@item{If it is a (syntax-wrapped) pair whose first element is an
|
||||
@item{If it is a syntax-object pair whose first element is an
|
||||
identifier, then the identifier's binding is used (as in the
|
||||
preceding case).}
|
||||
|
||||
@item{If it is a (syntax-wrapped) pair, then the symbol
|
||||
@scheme['#%app] is wrapped with the lexical context of the
|
||||
pair's syntax wrapper. If the resulting @scheme[#%app]
|
||||
identifier has no binding, parsing fails with an
|
||||
@scheme[exn:fail:syntax] exception. Otherwise, the new
|
||||
identifier is @scheme[cons]ed with the pair, and then the pair
|
||||
is wrapped using the same context as the @scheme[#%app]
|
||||
identifier, and parsing starts again (i.e., it continues with
|
||||
the preceding case).}
|
||||
@item{If it is a syntax-object pair, then a new syntax-object symbol
|
||||
@scheme['#%app] is created using the lexical context of the
|
||||
pair. If the resulting @scheme[#%app] identifier has no
|
||||
binding, parsing fails with an @scheme[exn:fail:syntax]
|
||||
exception. Otherwise, the new identifier is combined with the
|
||||
original pair to form a new syntax-object pair (using the same
|
||||
context as the original pair), and parsing starts again (i.e.,
|
||||
it continues with the preceding case).}
|
||||
|
||||
@item{If it is any other (syntax-wrapped) value, then the symbol
|
||||
@scheme['#%datum] is wrapped with the lexical context of the
|
||||
values syntax wrapper. If the resulting @scheme[#%datum]
|
||||
identifier has no binding, parsing fails with an
|
||||
@scheme[exn:fail:syntax] exception. Otherwise, the new
|
||||
identifier is @scheme[cons]ed with the pair, and then the pair
|
||||
is wrapped using the same context; parsing starts again (i.e.,
|
||||
it continues with the second case above).}
|
||||
@item{If it is any other syntax object, then a new syntax-object
|
||||
symbol @scheme['#%datum] is created using the lexical context
|
||||
of the original syntax object. If the resulting
|
||||
@scheme[#%datum] identifier has no binding, parsing fails with
|
||||
an @scheme[exn:fail:syntax] exception. Otherwise, the new
|
||||
identifier is combined with the original syntax object in a new
|
||||
syntax-object pair (using the same context as the original
|
||||
pair), and parsing starts again (i.e., it continues with the
|
||||
second case above).}
|
||||
|
||||
}
|
||||
|
||||
For either of the first two steps, if the identifier has no binding,
|
||||
then the symbol @scheme['#%top] is wrapped with the same lexical
|
||||
context as the identifier; is this @scheme[#%top] identifier has no
|
||||
binding, then parsing fails with an @scheme[exn:fail:syntax]
|
||||
exception. Otherwise, parsing starts again, using the binding for
|
||||
@scheme[#%top].
|
||||
then a new syntax-object symbol @scheme['#%top] is created using the
|
||||
lexical context of the identifier; if this @scheme[#%top] identifier
|
||||
has no binding, then parsing fails with an @scheme[exn:fail:syntax]
|
||||
exception. Otherwise, the new identifier is combined with the
|
||||
original identifier in a new syntax-object pair (using the same
|
||||
context as the original identifier), and parsing starts again.
|
||||
|
||||
Thus, the possibilities that do not fail lead to an identifier with a
|
||||
particular binding. This binding refers to one of three things:
|
||||
|
@ -55,24 +56,24 @@ particular binding. This binding refers to one of three things:
|
|||
associated value is to a procedure of one argument, the
|
||||
procedure is called as a syntax transformer (see
|
||||
@secref["transformers"]), and parsing starts again with the
|
||||
syntax result. If the transformer binding is to any other kind
|
||||
of value, parsing fails with an @scheme[exn:fail:syntax]
|
||||
exception.}
|
||||
syntax-object result. If the transformer binding is to any
|
||||
other kind of value, parsing fails with an
|
||||
@scheme[exn:fail:syntax] exception.}
|
||||
|
||||
@item{A variable binding, such as introduced by a module-level
|
||||
@scheme[define] or by @scheme[let]. In this case, if the form
|
||||
being parsed is just an identifier, then it is parsed as a
|
||||
run-time reference to the location of the corersponding
|
||||
variable. If the form being parsed is a (syntax-wrapped) list,
|
||||
then an @scheme[#%app] is added to the from of the list in the
|
||||
same way as when the kfirst thing in the list is not an
|
||||
identifier (third case in the prvious enumeration), and parsing
|
||||
continues.}
|
||||
variable. If the form being parsed is a syntax-object list,
|
||||
then an @scheme[#%app] is added to the front of the
|
||||
syntax-object list in the same way as when the first item in
|
||||
the syntax-object list is not an identifier (third case in the
|
||||
previous enumeration), and parsing continues.}
|
||||
|
||||
@item{Core syntax, which is parsed as described in the reminder of
|
||||
this section. Parsing core syntactic forms typically involves
|
||||
recursive parsing of sub-forms, and may introduce bindings that
|
||||
control the parsing of sub-forms.}
|
||||
@item{Core syntax, which is parsed as described in
|
||||
@secref["mz:syntax"]. Parsing core syntactic forms typically
|
||||
involves recursive parsing of sub-forms, and may introduce
|
||||
bindings that control the parsing of sub-forms.}
|
||||
|
||||
}
|
||||
|
||||
|
@ -101,58 +102,101 @@ possible contexts are as follows:
|
|||
|
||||
}
|
||||
|
||||
Different core syntax forms parse sub-forms in different contexts. For
|
||||
example, a @scheme[let] form always parses the right-hand expressions
|
||||
of a binding in an expression context, but it starts parsing the body
|
||||
in an internal-definition context.
|
||||
|
||||
@section[#:tag "mz:intdef-body"]{Internal Definitions}
|
||||
|
||||
@section{Fully Expanded Programs}
|
||||
An internal-definition context corresponds to a partial expansion
|
||||
step. A form that supports internal definitions starts by expanding
|
||||
its first form in an internal-definition context, but only
|
||||
partially. That is, it recursively expands only until the form becomes
|
||||
one of the following:
|
||||
|
||||
@itemize{
|
||||
|
||||
@item{A @scheme[define-values] or @scheme[define-syntaxes] form: The
|
||||
definition form is not expanded further. Instead, the next form
|
||||
is expanded partially, and so on. As soon as an expression form
|
||||
is found, the accumulated definition forms are converted to a
|
||||
@scheme[letrec-values] (if no @scheme[define-syntaxes] forms
|
||||
were found) or @scheme[letrec-syntaxes+values] form, moving the
|
||||
expression forms to the body to be expanded in expression
|
||||
context.
|
||||
|
||||
When a @scheme[define-values] form is discovered, the lexical
|
||||
context of all syntax objects for the body sequence is
|
||||
immediately enriched with bindings for the
|
||||
@scheme[define-values] form before expansion continues. When a
|
||||
@scheme[define-syntaxes] form is discovered, the right-hand
|
||||
side is executed and a transformer binding is installed before
|
||||
expansion continues.}
|
||||
|
||||
@item{A primitive expression form other than @scheme[begin]: The
|
||||
expression will be further expanded in an expression context,
|
||||
along with all remaining body forms. If any definitions were
|
||||
found, this expansion takes place after conversion to a
|
||||
@scheme[letrec-values] or @scheme[letrec-syntaxes+values]
|
||||
form. Otherwise, the expressions are expanded immediately in an
|
||||
expression context.}
|
||||
|
||||
@item{A @scheme[begin] form: The sub-forms of the @scheme[begin] are
|
||||
spliced into the internal-definition sequence, and partial
|
||||
expansion continues with the first of the newly-spliced forms
|
||||
(or the next form, if the @scheme[begin] had no sub-forms).}
|
||||
|
||||
}
|
||||
|
||||
@section[#:tag "mz:fully-expanded"]{Fully Expanded Programs}
|
||||
|
||||
A fully expanded program---that is, a parsed program---is represented
|
||||
in the same way as an unparsed program: as a syntax-wrapped
|
||||
combination of symbols, pairs, and other values. However, a fully
|
||||
expanded program fits a specific grammar.
|
||||
in the same way as an unparsed program: as a syntax-object. However, a
|
||||
fully expanded program fits a specific grammar.
|
||||
|
||||
@schemeblock[
|
||||
#, @is-one-of[@scheme[_top-level-expr]]
|
||||
_general-top-level-expr
|
||||
(#%expression _expr)
|
||||
(module _id _name-id
|
||||
(#%plain-module-begin _module-level-expr ...))
|
||||
(begin _top-level-expr ...)
|
||||
code:blank
|
||||
#, @is-one-of[@scheme[_module-level-expr]]
|
||||
_general-top-level-expr
|
||||
(provide _provide-spec ...)
|
||||
code:blank
|
||||
#, @is-one-of[@scheme[_general-top-level-expr]]
|
||||
_expr
|
||||
(define-values (_id ...) _expr)
|
||||
(define-syntaxes (_id ...) _expr)
|
||||
(define-values-for-syntax (_id ...) _expr)
|
||||
(require _require-spec ...)
|
||||
(require-for-syntax _require-spec ...)
|
||||
(require-for-template _require-spec ...)
|
||||
code:blank
|
||||
#, @is-one-of[@scheme[_expr]]
|
||||
_id
|
||||
(lambda _formals _expr ...+)
|
||||
(case-lambda (_formals _expr ...+) ...)
|
||||
(if _expr _expr)
|
||||
(if _expr _expr _expr)
|
||||
(begin _expr ...+)
|
||||
(begin0 _expr _expr ...)
|
||||
(let-values (((_id ...) _expr) ...) _expr ...+)
|
||||
(letrec-values (((_id ...) _expr) ...) _expr ...+)
|
||||
(set! _id _expr)
|
||||
(#, @scheme[quote] _datum)
|
||||
(quote-syntax _datum)
|
||||
(with-continuation-mark _expr _expr _expr)
|
||||
(#%app _expr ...+)
|
||||
(#%datum . _datum)
|
||||
(#%top . _id)
|
||||
(#%variable-reference _id)
|
||||
(#%variable-reference (#%top . _id))
|
||||
code:blank
|
||||
#, @is-one-of[@scheme[_formals]]
|
||||
(_id ...)
|
||||
(_id ...+ . _id)
|
||||
_id
|
||||
]
|
||||
@schemegrammar*[
|
||||
#:literals (#%expression module #%plain-module-begin begin provide
|
||||
define-values define-syntaxes define-values-for-syntax
|
||||
require require-for-syntax require-for-template
|
||||
#%plain-lambda case-lambda if begin begin0 let-values letrec-values
|
||||
set! quote-syntax quote with-continuation-mark
|
||||
#%plain-app #%datum #%top #%variable-reference)
|
||||
[top-level-form general-top-level-form
|
||||
(#%expression expr)
|
||||
(module id name-id
|
||||
(#%plain-module-begin
|
||||
module-level-form ...))
|
||||
(begin top-level-form ...)]
|
||||
[module-level-form general-top-level-form
|
||||
(provide provide-spec ...)]
|
||||
[general-top-level-form expr
|
||||
(define-values (id ...) expr)
|
||||
(define-syntaxes (id ...) expr)
|
||||
(define-values-for-syntax (id ...) expr)
|
||||
(require require-spec ...)
|
||||
(require-for-syntax require-spec ...)
|
||||
(require-for-template require-spec ...)]
|
||||
[expr id
|
||||
(#%plain-lambda formals expr ...+)
|
||||
(case-lambda (formals expr ...+) ...)
|
||||
(if expr expr)
|
||||
(if expr expr expr)
|
||||
(begin expr ...+)
|
||||
(begin0 expr expr ...)
|
||||
(let-values (((id ...) expr) ...)
|
||||
expr ...+)
|
||||
(letrec-values (((id ...) expr) ...)
|
||||
expr ...+)
|
||||
(set! id expr)
|
||||
(#, @scheme[quote] datum)
|
||||
(quote-syntax datum)
|
||||
(with-continuation-mark expr expr expr)
|
||||
(#%plain-app expr ...+)
|
||||
(#%datum . datum)
|
||||
(#%top . id)
|
||||
(#%variable-reference id)
|
||||
(#%variable-reference (#%top . id))]
|
||||
[formals (id ...)
|
||||
(id ...+ . id)
|
||||
id]]
|
||||
|
|
|
@ -137,7 +137,7 @@ each of its sub-expression. In addtion, some procedures (notably
|
|||
a certain number of values.
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Top-Level and Module-Level Bindings}
|
||||
@section{Top-Level and Module-Level Variables}
|
||||
|
||||
Given
|
||||
|
||||
|
@ -147,7 +147,7 @@ then an algebra student simplifies @tt{x + 1} as follows:
|
|||
|
||||
@verbatim{ x + 1 = 10 + 1 = 11}
|
||||
|
||||
Scheme works much the same way, in that a set of top-level bindings
|
||||
Scheme works much the same way, in that a set of top-level variables
|
||||
are available for substitutions on demand during evaluation. For
|
||||
example, given
|
||||
|
||||
|
@ -191,7 +191,7 @@ a module is essentially a prefix on a defined name, so that different
|
|||
modules can define the name.
|
||||
|
||||
Using @scheme[set!], a program can change the value associated with an
|
||||
existing top-level binding:
|
||||
existing top-level variable:
|
||||
|
||||
@prog-steps/no-obj[
|
||||
[{(define x 10)}
|
||||
|
@ -208,7 +208,7 @@ existing top-level binding:
|
|||
@section{Objects and Imperative Update}
|
||||
|
||||
In addition to @scheme[set!] for imperative update of top-level
|
||||
bindings, various procedures enable the modification of elements
|
||||
variables, various procedures enable the modification of elements
|
||||
within a compound data structure. For example, @scheme[vector-set!]
|
||||
modifies the content of a vector.
|
||||
|
||||
|
@ -292,8 +292,8 @@ create objects, such as @scheme[vector], add to the set of objects:
|
|||
11]
|
||||
]
|
||||
|
||||
The distinction between a top-level binding is an object reference is
|
||||
crucial. A top-level binding is not a value; each time a binding
|
||||
The distinction between a top-level variable is an object reference is
|
||||
crucial. A top-level variable is not a value; each time a variable
|
||||
expression is evaluated, the value is extracted from the current set
|
||||
of definitions. An object reference, in contrast is a value, and
|
||||
therefore needs no further evaluation. The model evaluation steps
|
||||
|
@ -409,14 +409,14 @@ new location:
|
|||
17]
|
||||
]
|
||||
|
||||
A location is the same as a top-level binding, but when a location is
|
||||
A location is the same as a top-level variable, but when a location is
|
||||
generated, it (conceptually) uses a name that has not been used before
|
||||
and that cannot not be generated again or accessed directly.
|
||||
|
||||
Generating a location in this way means that @scheme[set!] evaluates
|
||||
for local variables in the same way as for top-level bindings, because
|
||||
the variable is always replaced with a location by the time the
|
||||
@scheme[set!] form is evaluated:
|
||||
for local variables in the same way as for top-level variables,
|
||||
because the local variable is always replaced with a location by the
|
||||
time the @scheme[set!] form is evaluated:
|
||||
|
||||
@prog-steps[
|
||||
[{(define <p1> (lambda (x) (begin (set! x 3) x)))}
|
||||
|
@ -459,7 +459,7 @@ instance of @scheme[x] in @scheme[_expr].
|
|||
@section{Identifiers, Variables, and Locations}
|
||||
|
||||
A @defterm{variable} is a placeholder for a value, and an expressions
|
||||
in an initial program refer to variables. A top-level binding is both
|
||||
in an initial program refer to variables. A top-level variable is both
|
||||
a variable and a location. Any other variable is always replaced by a
|
||||
location at run-time, so that evaluation of expressions involves only
|
||||
locations. A single non-top-level variable, such as a procedure
|
||||
|
@ -509,21 +509,87 @@ The syntax of a Scheme program is defined by
|
|||
|
||||
}
|
||||
|
||||
For details on the read phase, see @secref["mz:reader"]. Source code is
|
||||
normally read in @scheme[read-syntax] mode, otherwise it must be
|
||||
converted to syntax using @scheme[datum->syntax-object]; the expand
|
||||
phase is defined in terms of syntax objects.
|
||||
For details on the read phase, see @secref["mz:reader"]. Source code
|
||||
is normally read in @scheme[read-syntax] mode, otherwise it must be
|
||||
converted to syntax using @scheme[datum->syntax]; the expand phase is
|
||||
defined in terms of syntax objects.
|
||||
|
||||
Expansion recursively processes a syntax-wrapped datum; for details,
|
||||
see @secref["mz:expansion"]. Ultimately, expansion leads to the
|
||||
synactic forms described in @secref["mz:syntax"].
|
||||
An identifier, for example, is a syntax-object symbol, and the
|
||||
identifier's binding is determined by lexical information attached to
|
||||
the identifier. Expansion recursively processes a syntax object,
|
||||
both using its lexical information and extending the information for
|
||||
nested objects. For details, see @secref["mz:expansion"].
|
||||
|
||||
...
|
||||
Ultimately, expansion produces a syntax object matching the grammar
|
||||
of the forms in @secref["mz:fully-expanded"]. This fully-expanded
|
||||
datum corresponds to a parsed expression, and lexical information on
|
||||
its identifiers indicates the parse. For example, a @scheme[car]
|
||||
identifier might have lexical information that designates it as the
|
||||
@scheme[car] from the @schememodname[big] language (i.e., the built-in
|
||||
@scheme[car]). Similarly, a @scheme[lambda] identifier's lexical
|
||||
information may indicate that it represents a procedure form.
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Namespaces}
|
||||
|
||||
A @idefterm{namespace} is a top-level mapping from symbols to binding
|
||||
information. It is the starting point for expanding an expression; a
|
||||
syntax object produced by @scheme[read-syntax] has no initial
|
||||
lexical context; the syntax object can be expanded after
|
||||
initializing it with the mappings of a particular namespace.
|
||||
|
||||
A namespace maps each symbol to one of three possible bindings:
|
||||
|
||||
@itemize{
|
||||
|
||||
@item{a particular module-level binding from a particular module}
|
||||
|
||||
@item{a top-level transformer binding named by the symbol}
|
||||
|
||||
@item{a top-level variable named by the symbol}
|
||||
|
||||
}
|
||||
|
||||
An ``empty'' namespace maps all symbols to top-level
|
||||
variables. Importing a module into the top-level adjusts the namespace
|
||||
bindings for all of the imported named. Evaluating a top-level
|
||||
@scheme[define] form updates the namespace's mapping to refer to a
|
||||
variable (if it does not already) and installs a value into the
|
||||
variable.
|
||||
|
||||
In addition to its main mapping, each namespace encapsulates a
|
||||
distinct set of top-level variables, as well as a potentially distinct
|
||||
set of module instances. After a namespace is created, module
|
||||
instances from existing namespaces can be attached to the new
|
||||
namespace.
|
||||
|
||||
At all times during evaluation, some namespace is designated as the
|
||||
@defterm{current namespace}. The current namespace has no particular
|
||||
relationship, however, with the namespace used to expand the code that
|
||||
is executing. Furthermore, a namespace is purely a top-level concept;
|
||||
it does not encapsulate the full environment of an expression within
|
||||
local binding forms.
|
||||
|
||||
In terms of the evaluation model, top-level variables from different
|
||||
namespaces essentially correspond to definitions with different
|
||||
prefixes. In particular, changing the current namespace during
|
||||
evaluation does not change the variables to which executing
|
||||
expressions refer.
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Threads}
|
||||
|
||||
Scheme supports multiple, pre-emptive threads of evaluation. In terms
|
||||
of the evaluation model, this means that each step in evaluation
|
||||
actually consists of multiple concurrent expressions, rather than a
|
||||
single expression. The expressions all share the same objects and
|
||||
top-level variables, so that they can communicate through shared
|
||||
state. Most evaluation steps involve a single step in a single
|
||||
expression, but certain synchronization primitives require multiple
|
||||
threads to progress together in one step.
|
||||
|
||||
In addition to shared state, each thread has its own private state
|
||||
that is accessed through @defterm{thread cells} and
|
||||
@defterm{parameters}. In particular, the current namespace is a
|
||||
thread-specific property implemented by a parameter; it is not a
|
||||
global property.
|
||||
|
|
|
@ -144,6 +144,9 @@ according to their order in the application form.
|
|||
(#%app cons)
|
||||
]}
|
||||
|
||||
@defform[(#%plain-app proc-expr arg-expr ...)]{
|
||||
Like @scheme[#%app], but without support for keyword arguments.
|
||||
}
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section[#:tag "mz:lambda"]{Procedure Expressions: @scheme[lambda] and @scheme[case-lambda]}
|
||||
|
@ -284,6 +287,10 @@ support keyword and optional arguments.
|
|||
(f 1 2 3)))
|
||||
]}
|
||||
|
||||
@defform[(#%plain-lambda formals body ...+)]{
|
||||
Like @scheme[lambda], but without support for keyword or optional arguments.
|
||||
}
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Local Binding: @scheme[let], @scheme[let*], and @scheme[letrec]}
|
||||
|
||||
|
@ -513,10 +520,31 @@ ignoring the @scheme[body] results. The results of the @scheme[expr]
|
|||
are the results of the @scheme[begin0] form, but the @scheme[expr] is
|
||||
in tail position only if no @scheme[body]s are present.
|
||||
|
||||
|
||||
|
||||
@examples[
|
||||
(begin0
|
||||
(values 1 2)
|
||||
(printf "hi\n"))
|
||||
]}
|
||||
]}
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Continuation Marks: @scheme[with-continuation-marks]}
|
||||
|
||||
@defform[(with-continuation-mark key-expr val-expr result-expr)]{
|
||||
Evaluates @scheme[key-expr] and @scheme[val-expr] in order to obtain a key and
|
||||
value, respectively. The key and value are attached as a mark to the
|
||||
current continuation frame (see @secref["mz:contmarks"]), and then
|
||||
@scheme[result-expr] is evaluated in tail position.
|
||||
}
|
||||
|
||||
@;------------------------------------------------------------------------
|
||||
@section{Syntax Quoting: @scheme[quote-syntax]}
|
||||
|
||||
@defform[(quote-syntax datum)]{
|
||||
Produces a syntax object that preserves
|
||||
lexical and source-location information attached to @scheme[datum]
|
||||
at expansion time.
|
||||
|
||||
@examples[
|
||||
(syntax? (quote-syntax x))
|
||||
]
|
||||
}
|
Loading…
Reference in New Issue
Block a user