doc and scribble work

svn: r6431
This commit is contained in:
Matthew Flatt 2007-06-01 06:28:46 +00:00
parent a921007b32
commit 4736768878
17 changed files with 781 additions and 322 deletions

View File

@ -103,6 +103,7 @@
(cond
[(table? p) (collect-table p ht)]
[(itemization? p) (collect-itemization p ht)]
[(blockquote? p) (collect-blockquote p ht)]
[(delayed-flow-element? p) (void)]
[else (collect-paragraph p ht)]))
@ -114,6 +115,10 @@
(for-each (lambda (d) (collect-flow d ht))
(itemization-flows i)))
(define/public (collect-blockquote i ht)
(for-each (lambda (d) (collect-flow-element d ht))
(blockquote-paragraphs i)))
(define/public (collect-element i ht)
(when (target-element? i)
(collect-target-element i ht))
@ -189,6 +194,7 @@
(cond
[(table? p) (render-table p part ht)]
[(itemization? p) (render-itemization p part ht)]
[(blockquote? p) (render-blockquote p part ht)]
[(delayed-flow-element? p) (render-flow-element
((delayed-flow-element-render p) this part ht)
part ht)]
@ -202,6 +208,10 @@
(map (lambda (d) (render-flow d part ht))
(itemization-flows i)))
(define/public (render-blockquote i part ht)
(map (lambda (d) (render-flow-element d part ht))
(blockquote-paragraphs i)))
(define/public (render-element i part ht)
(cond
[(and (link-element? i)

View File

@ -71,10 +71,7 @@
(title-decl-content (car l))
(title-decl-tag (car l))
(title-decl-style (car l)))]
[(or (paragraph? (car l))
(table? (car l))
(itemization? (car l))
(delayed-flow-element? (car l)))
[(flow-element? (car l))
(let ([para (decode-accum-para accum)]
[part (decode-flow* (cdr l) tag style title part-depth)])
(make-styled-part (part-tag part)

View File

@ -201,6 +201,15 @@
(cons #f (map (lambda (x) #f) flows)))))))
(table-flowss t)))))
(define/override (render-blockquote t part ht)
`((blockquote ,@(if (string? (blockquote-style t))
`(((class ,(blockquote-style t))))
null)
,@(apply append
(map (lambda (i)
(render-flow-element i part ht))
(blockquote-paragraphs t))))))
(define/override (render-itemization t part ht)
`((ul
,@(map (lambda (flow)

View File

@ -14,6 +14,7 @@
(define/override (get-suffix) #".tex")
(inherit render-flow
render-flow-element
render-content
install-file
format-number
@ -50,6 +51,7 @@
(printf "\\newcommand{\\textsub}[1]{$_{#1}$}\n")
(printf "\\newcommand{\\textsuper}[1]{$^{#1}$}\n")
(printf "\\newcommand{\\refcontent}[1]{#1}\n")
(printf "\\definecolor{PaleBlue}{rgb}{0.90,0.90,1.0}\n")
(printf "\\definecolor{LightGray}{rgb}{0.90,0.90,0.90}\n")
(printf "\\newcommand{\\schemeinput}[1]{\\colorbox{LightGray}{\\hspace{-0.5ex}\\schemeinputcol{#1}\\hspace{-0.5ex}}}\n")
(printf "\\begin{document}\n")
@ -153,7 +155,13 @@
(if index?
(printf "\n\n\\begin{theindex}\n")
(printf "\n\n~a\\begin{~a}~a{@{}~a}\n"
(if boxed? "\\vspace{4ex}\\hrule\n\\vspace{-2ex}\n" "")
(if boxed?
(format "{~a\\begin{picture}(1,0)\\put(0,0){\\line(1,0){1}}\\end{picture}}~a\n\\nopagebreak\n"
"\\setlength{\\unitlength}{\\linewidth}"
(if (equal? tableform "longtable")
"\\vspace{-5ex}"
"\n\n"))
"")
tableform
opt
(apply string-append
@ -185,6 +193,15 @@
(printf "\n\n\\end{itemize}\n")
null)
(define/override (render-blockquote t part ht)
(printf "\n\n\\begin{quote}\n")
(parameterize ([current-table-depth (add1 (current-table-depth))])
(for-each (lambda (e)
(render-flow-element e part ht))
(blockquote-paragraphs t)))
(printf "\n\n\\end{quote}\n")
null)
(define/override (render-other i part ht)
(cond
[(string? i) (display-protected i)]

View File

@ -137,7 +137,7 @@
;; ----------------------------------------
(provide defproc defproc* defstruct defthing defform
(provide defproc defproc* defstruct defthing defform defform/none
specsubform specsubform/inline
var svar void-const)
@ -174,7 +174,11 @@
#'name)
#'rest)
#'spec)])])
#'(*defform 'spec (lambda (x) (schemeblock0 new-spec)) (lambda () (list desc ...))))]))
#'(*defform #t 'spec (lambda (x) (schemeblock0 new-spec)) (lambda () (list desc ...))))]))
(define-syntax (defform/none stx)
(syntax-case stx ()
[(_ spec desc ...)
#'(*defform #f 'spec (lambda (ignored) (schemeblock0 spec)) (lambda () (list desc ...)))]))
(define-syntax specsubform
(syntax-rules ()
[(_ spec desc ...)
@ -375,11 +379,15 @@
(to-element result-contract))))))))
(content-thunk))))
(define (*defform form form-proc content-thunk)
(define (meta-symbol? s) (memq s '(... ...+ ?)))
(define (*defform kw? form form-proc content-thunk)
(parameterize ([current-variable-list
(let loop ([form (cdr form)])
(let loop ([form (if kw? (cdr form) form)])
(cond
[(symbol? form) (list form)]
[(symbol? form) (if (meta-symbol? form)
null
(list form))]
[(pair? form) (append (loop (car form))
(loop (cdr form)))]
[else null]))])
@ -397,26 +405,36 @@
(to-element
`(,x
. ,(cdr form)))))))
(make-target-element
#f
(list (to-element (car form)))
(register-scheme-form-definition (car form)))))))))
(and kw?
(make-target-element
#f
(list (to-element (car form)))
(register-scheme-form-definition (car form))))))))))
(content-thunk)))))
(define (*specsubform form form-thunk content-thunk)
(parameterize ([current-variable-list
(let loop ([form form])
(cond
[(symbol? form) (list form)]
[(pair? form) (append (loop (car form))
(loop (cdr form)))]
[else null]))])
(make-splice
(append (let loop ([form form])
(cond
[(symbol? form) (if (meta-symbol? form)
null
(list form))]
[(pair? form) (append (loop (car form))
(loop (cdr form)))]
[else null]))
(current-variable-list))])
(make-blockquote
"leftindent"
(cons
(if form-thunk
(form-thunk)
(to-element form))
(content-thunk)))))
(make-table
'boxed
(list (list
(make-flow
(list
(if form-thunk
(form-thunk)
(make-paragraph (list (to-element form)))))))))
(flow-paragraphs (decode-flow (content-thunk)))))))
(define (*var id)
(to-element (*var-sym id)))
@ -451,6 +469,17 @@
(index (string-append (content->string (element-content c)) "s")
c)))
(provide pidefterm)
;; ----------------------------------------
(provide where-is-one-of
is-one-of)
(define (where-is-one-of id)
(make-element #f (list "where " id " is one of")))
(define (is-one-of id)
(make-element #f (list id " is one of")))
;; ----------------------------------------

View File

@ -71,22 +71,25 @@
(make-element 'tt (list v)))
content))
(set! dest-col (+ dest-col (if (string? v) (string-length v) 1)))))))
(define (advance c init-line!)
(let ([c (syntax-column c)]
[l (syntax-line c)]
[span (syntax-span c)])
(when (and l (l . > . line))
(out "\n" no-color)
(set! line l)
(init-line!))
(when c
(let ([d-col (hash-table-get col-map src-col src-col)])
(let ([amt (+ (- c src-col) (- d-col dest-col))])
(when (positive? amt)
(let ([old-dest-col dest-col])
(out (make-element 'hspace (list (make-string amt #\space))) #f)
(set! dest-col (+ old-dest-col amt))))))
(set! src-col (+ c (or span 1))))))
(define advance
(case-lambda
[(c init-line! delta)
(let ([c (+ delta (syntax-column c))]
[l (syntax-line c)]
[span (syntax-span c)])
(when (and l (l . > . line))
(out "\n" no-color)
(set! line l)
(init-line!))
(when c
(let ([d-col (hash-table-get col-map src-col src-col)])
(let ([amt (+ (- c src-col) (- d-col dest-col))])
(when (positive? amt)
(let ([old-dest-col dest-col])
(out (make-element 'hspace (list (make-string amt #\space))) #f)
(set! dest-col (+ old-dest-col amt))))))
(set! src-col (+ c (or span 1)))))]
[(c init-line!) (advance c init-line! 0)]))
(define (convert-infix c quote-depth)
(let ([l (syntax->list c)])
(and l
@ -240,7 +243,8 @@
((loop init-line! quote-depth) (car l))
(lloop (cdr l))]
[else
(out " . " (if (positive? quote-depth) value-color paren-color))
(advance l init-line! -2)
(out ". " (if (positive? quote-depth) value-color paren-color))
(set! src-col (+ src-col 3))
(hash-table-put! col-map src-col dest-col)
((loop init-line! quote-depth) l)]))

View File

@ -26,6 +26,11 @@
border: 0.5em solid #F5F5DC;
}
.leftindent {
margin-left: 1em;
margin-right: 0em;
}
h1,h2,h3,h4,h5,h6 {
margin-top: .5em;
}

View File

@ -48,6 +48,7 @@
(or (paragraph? p)
(table? p)
(itemization? p)
(blockquote? p)
(delayed-flow-element? p)))
(provide-structs
@ -65,6 +66,8 @@
[flowss (listof (listof flow?))])]
[delayed-flow-element ([render (any/c part? any/c . -> . flow-element?)])]
[itemization ([flows (listof flow?)])]
[blockquote ([style any/c]
[paragraphs (listof flow-element?)])]
;; content = list of elements
[element ([style any/c]
[content list?])]

View File

@ -124,7 +124,7 @@ The full syntax of @scheme[for] is
(for (_clause ...)
_body-expr ...+)
code:blank
#, @elem{where} _clause #, @elem{is one of}
#, @where-is-one-of[@scheme[_clause]]
[_id _sequence-expr]
#:when _boolean-expr
]
@ -381,18 +381,18 @@ iterate. Specifically, the clause should have one of the following
@scheme[_fast-clause] forms:
@schemeblock[
#, @elem{a} _fast-clause #, @elem{is one of}
[_id (in-range _expr)]
[_id (in-range _expr _expr)]
[_id (in-range _expr _expr _expr)]
[_id (in-naturals)]
[_id (in-naturals _expr)]
[_id (in-list _expr)]
[_id (in-vector _expr)]
[_id (in-string _expr)]
[_id (in-bytes _expr)]
[_id (stop-before _fast-clause _predicate-expr)]
[_id (stop-after _fast-clause _predicate-expr)]
#, @is-one-of[@scheme[_fast-clause]]
[_id (in-range _expr)]
[_id (in-range _expr _expr)]
[_id (in-range _expr _expr _expr)]
[_id (in-naturals)]
[_id (in-naturals _expr)]
[_id (in-list _expr)]
[_id (in-vector _expr)]
[_id (in-string _expr)]
[_id (in-bytes _expr)]
[_id (stop-before _fast-clause _predicate-expr)]
[_id (stop-after _fast-clause _predicate-expr)]
]
@examples[
@ -413,11 +413,11 @@ In the case of @scheme[for-values] forms, a few more
the obvious variants of @scheme[_fast-clause] forms:
@schemeblock[
#, @elem{a} _fast-values-clause #, @elem{is one of}
[(_id) (in-range _expr)]
...
[(_id _id) (in-indexed _fast-clause)]
[(_id ...) (in-parallel _fast-clause ...)]
#, @is-one-of[@scheme[_fast-values-clause]]
[(_id) (in-range _expr)]
...
[(_id _id) (in-indexed _fast-clause)]
[(_id ...) (in-parallel _fast-clause ...)]
]
The grammars above are not complete, because the set of syntactic

View File

@ -1,11 +1,13 @@
#reader(lib "docreader.ss" "scribble")
@require["mz.ss"]
@title{Core Datatypes}
@title[#:style 'toc]{Built-In Datatypes}
Each of the built-in datatypes comes with a set of procedures for
manipulating members of the datatype.
@local-table-of-contents[]
@; ------------------------------------------------------------
@section[#:tag "booleans"]{Booleans}
@ -191,8 +193,6 @@ If the @scheme[lst]s are empty, then @scheme[#f] is returned.}
@section[#:tag "procedures"]{Procedures}
@section[#:tag "promises"]{Promises}
@; ----------------------------------------------------------------------
@section[#:tag "void"]{Void and Undefined}

View File

@ -0,0 +1,154 @@
#reader(lib "docreader.ss" "scribble")
@require["mz.ss"]
@title[#:tag "mz:expansion"]{Syntax Expansion}
Expansion recursively processes a syntax-wrapped datum 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
@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.}
@item{If it is a (syntax-wrapped) 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 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).}
}
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].
Thus, the possibilities that do not fail lead to an identifier with a
particular binding. This binding refers to one of three things:
@itemize{
@item{A transformer binding, such as introduced by
@scheme[define-syntax] or @scheme[let-syntax]. If the
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.}
@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.}
@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.}
}
Each expansion step occurs in a particular context, and transformers
and core-syntax parsing can depend on the context. For example, a
@scheme[module] form is allowed only in a top-level context. The
possible contexts are as follows:
@itemize{
@item{@defterm{top level} : outside of any module, definition, or
expression, except that sub-expressions of a top-level
@scheme[begin] form are also expanded as top-level forms.}
@item{@defterm{module begin} : inside the body of a module, as the
only form within the module.}
@item{@defterm{module body} : in the body of a module (inside the
moudule-begin layer).}
@item{@defterm{internal definition} : in a nested context that allows
both definitions and expressions.}
@item{@defterm{expression} : in a context where only expressions are
allowed.}
}
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.
@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
]

View File

@ -67,6 +67,9 @@ exact, and when they are @scheme[=] (except for @scheme[+nan.0], as
noted above). Two numbers are @scheme[equal?] when they are
@scheme[eqv?].
@; ----------------------------------------
@section{Number Types}
@defproc[(number? [v any/c]) boolean?]{ Returns @scheme[#t] if @scheme[v]
is a number, @scheme[#f] otherwise.
@ -96,6 +99,32 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(integer? 1) (integer? 2.3) (integer? 4.0) (integer? 2+3i) (integer? "hello")]}
@defproc[(zero? [z number?]) boolean?]{ Returns @scheme[(= 0 z)].
@examples[(zero? 0) (zero? -0.0)]}
@defproc[(positive? [x real?]) boolean?]{ Returns @scheme[(> x 0)].
@examples[(positive? 10) (positive? -10) (positive? 0.0)]}
@defproc[(negative? [x real?]) boolean?]{ Returns @scheme[(< x 0)].
@examples[(negative? 10) (negative? -10) (negative? -0.0)]}
@defproc[(even? [n integer?]) boolean?]{ Returns @scheme[(zero? (modulo
n 2))].
@examples[(even? 10.0) (even? 11) (even? +inf.0)]}
@defproc[(odd? [n integer?]) boolean?]{ Returns @scheme[(not (even? n))].
@examples[(odd? 10.0) (odd? 11) (odd? +inf.0)]}
@defproc[(exact? [z number?]) boolean?]{ Returns @scheme[#t] if @scheme[z]
is an exact number, @scheme[#f] otherwise.
@ -122,6 +151,9 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(exact->inexact 1) (exact->inexact 1.0)]}
@; ----------------------------------------
@section{Arithmetic}
@defproc[(+ [z number?] ...0) number?]{ Returns the sum of the
@scheme[z]s, adding pairwise from left to right. If no arguments are
provided, the result is @scheme[0].
@ -197,60 +229,6 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(abs 1.0) (abs -1)]}
@defproc[(= [z number?] [w number?] ...1) boolean?]{ Returns
@scheme[#t] if all of the arguments are numerically equal,
@scheme[#f] otherwise. An inexact number is numerically equal to an
exact number when the exact coercion of the inexact number is the
exact number. Also, @scheme[0.0] and @scheme[-0.0] are numerically
equal, but @scheme[+nan.0] is not numerically equal to itself.
@examples[(= 1 1.0) (= 1 2) (= 2+3i 2+3i 2+3i)]}
@defproc[(< [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t] if
the arguments in the given order are in strictly increasing,
@scheme[#f] otherwise.
@examples[(< 1 1) (< 1 2 3) (< 1 +inf.0) (< 1 +nan.0)]}
@defproc[(<= [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t]
if the arguments in the given order are in non-decreasing,
@scheme[#f] otherwise.
@examples[(<= 1 1) (<= 1 2 1)]}
@defproc[(> [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t] if
the arguments in the given order are in strictly decreasing,
@scheme[#f] otherwise.
@examples[(> 1 1) (> 3 2 1) (> +inf.0 1) (< +nan.0 1)]}
@defproc[(>= [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t]
if the arguments in the given order are in non-increasing,
@scheme[#f] otherwise.
@examples[(>= 1 1) (>= 1 2 1)]}
@defproc[(zero? [z number?]) boolean?]{ Returns @scheme[(= 0 z)].
@examples[(zero? 0) (zero? -0.0)]}
@defproc[(positive? [x real?]) boolean?]{ Returns @scheme[(> x 0)].
@examples[(positive? 10) (positive? -10) (positive? 0.0)]}
@defproc[(negative? [x real?]) boolean?]{ Returns @scheme[(< x 0)].
@examples[(negative? 10) (negative? -10) (negative? -0.0)]}
@defproc[(max [x real?] ...1) boolean?]{ Returns the largest of the
@scheme[x]s, or @scheme[+nan.0] if any @scheme[x] is @scheme[+nan.0].
If any @scheme[x] is inexact, the result is coerced to inexact.
@ -265,17 +243,6 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(min 1 3 2) (min 1 3 2.0)]}
@defproc[(even? [n integer?]) boolean?]{ Returns @scheme[(zero? (modulo
n 2))].
@examples[(even? 10.0) (even? 11) (even? +inf.0)]}
@defproc[(odd? [n integer?]) boolean?]{ Returns @scheme[(not (even? n))].
@examples[(odd? 10.0) (odd? 11) (odd? +inf.0)]}
@defproc[(gcd [n integer?] ...0) integer?]{ Returns the greatest common
divisor of the @scheme[n]s. If no arguments are provided, the result is
@scheme[0].
@ -335,6 +302,77 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(denominator 5) (denominator 34/8) (denominator 2.3) (denominator +inf.0)]}
@; ----------------------------------------
@section{Number Comparison}
@defproc[(= [z number?] [w number?] ...1) boolean?]{ Returns
@scheme[#t] if all of the arguments are numerically equal,
@scheme[#f] otherwise. An inexact number is numerically equal to an
exact number when the exact coercion of the inexact number is the
exact number. Also, @scheme[0.0] and @scheme[-0.0] are numerically
equal, but @scheme[+nan.0] is not numerically equal to itself.
@examples[(= 1 1.0) (= 1 2) (= 2+3i 2+3i 2+3i)]}
@defproc[(< [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t] if
the arguments in the given order are in strictly increasing,
@scheme[#f] otherwise.
@examples[(< 1 1) (< 1 2 3) (< 1 +inf.0) (< 1 +nan.0)]}
@defproc[(<= [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t]
if the arguments in the given order are in non-decreasing,
@scheme[#f] otherwise.
@examples[(<= 1 1) (<= 1 2 1)]}
@defproc[(> [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t] if
the arguments in the given order are in strictly decreasing,
@scheme[#f] otherwise.
@examples[(> 1 1) (> 3 2 1) (> +inf.0 1) (< +nan.0 1)]}
@defproc[(>= [x real?] [y real?] ...1) boolean?]{ Returns @scheme[#t]
if the arguments in the given order are in non-increasing,
@scheme[#f] otherwise.
@examples[(>= 1 1) (>= 1 2 1)]}
@; ------------------------------------------------------------------------
@section{Powers and Roots}
@defproc[(sqrt [z number?]) number?]{ Returns the principal square root
of @scheme[z].The result is exact if @scheme[z] is exact and @scheme[z]'s
square root is rational. See also @scheme[integer-sqrt].
@examples[(sqrt 4/9) (sqrt 2) (sqrt -1)]}
@defproc[(integer-sqrt [n integer?]) integer?]{ Returns @scheme[(floor
(sqrt n))] for positive @scheme[n]. For negative @scheme[n], the result is
@scheme[(* (integer-sqrt (- n)) 0+i)].
@examples[(integer-sqrt 4.0) (integer-sqrt 5)]}
@defproc[(integer-sqrt/remainder [n integer?]) (values integer?
integer?)]{ Returns @scheme[(integer-sqrt n)] and @scheme[(- n (expt
(integer-sqrt n) 2))].
@examples[(integer-sqrt/remainder 4.0) (integer-sqrt/remainder 5)]}
@defproc[(expt [z number?] [w number?]) number?]{ Returns @scheme[z]
raised to the power of @scheme[w]. If @scheme[w] is exact @scheme[0],
the result is @scheme[1]. If @scheme[z] is exact @scheme[0] and
@scheme[w] is negative, the @exnraise[exn:fail:contract].
@examples[(expt 2 3) (expt 4 0.5) (expt +inf.0 0)]}
@defproc[(exp [z number?]) number?]{ Returns Euler's number raised to the
power of @scheme[z]. The result is normally inexact, but it is
@scheme[1] when @scheme[z] is an exact @scheme[0].
@ -349,6 +387,9 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(log (exp 1)) (log 2+3i) (log 1)]}
@; ------------------------------------------------------------------------
@section{Trigonometric Functions}
@defproc[(sin [z number?]) number?]{ Returns the sine of @scheme[z], where
@scheme[z] is in radians.
@ -385,33 +426,8 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(atan 0.5) (atan 2 1) (atan -2 -1) (atan 1+05.i)]
@defproc[(sqrt [z number?]) number?]{ Returns the principal square root
of @scheme[z].The result is exact if @scheme[z] is exact and @scheme[z]'s
square root is rational.
@examples[(sqrt 4/9) (sqrt 2) (sqrt -1)]}
@defproc[(integer-sqrt [n integer?]) integer?]{ Returns @scheme[(floor
(sqrt n))] for positive @scheme[n]. For negative @scheme[n], the result is
@scheme[(* (integer-sqrt (- n)) 0+i)].
@examples[(integer-sqrt 4.0) (integer-sqrt 5)]}
@defproc[(integer-sqrt/remainder [n integer?]) (values integer?
integer?)]{ Returns @scheme[(integer-sqrt n)] and @scheme[(- n (expt
(integer-sqrt n) 2))].
@examples[(integer-sqrt/remainder 4.0) (integer-sqrt/remainder 5)]}
@defproc[(expt [z number?] [w number?]) number?]{ Returns @scheme[z]
raised to the power of @scheme[w]. If @scheme[w] is exact @scheme[0],
the result is @scheme[1]. If @scheme[z] is exact @scheme[0] and
@scheme[w] is negative, the @exnraise[exn:fail:contract].
@examples[(expt 2 3) (expt 4 0.5) (expt +inf.0 0)]}
@; ------------------------------------------------------------------------
@section{Complex Numbers}
@defproc[(make-rectangular [x real?] [y real?]) number?]{ Returns
@scheme[(+ x (* y 0+1i))].
@ -448,6 +464,8 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(angle -3) (angle 3.0) (angle 3+4i) (angle +inf.0+inf.0i)]}
@; ------------------------------------------------------------------------
@section{Bitwise Operations}
@defproc[(bitwise-ior [n exact-integer?] ...0) exact-integer?]{ Returns
the bitwise ``inclusive or'' of the @scheme[n]s in their (semi-infinite)
@ -498,6 +516,8 @@ noted above). Two numbers are @scheme[equal?] when they are
@examples[(integer-length 8) (integer-length -8)]}
@; ------------------------------------------------------------------------
@section{Number--String Conversions}
@defproc[(number->string [z number?] [radix (one-of/c 2 8 10
16) 10]) string?]{ Returns a string that is the printed form of @scheme[z]

View File

@ -15,26 +15,7 @@
@define[(graph-defn) @elem{@litchar{#}@graph-tag[]@litchar{=}}]
@define[(graph-ref) @elem{@litchar{#}@graph-tag[]@litchar{#}}]
@title{Syntax}
The syntax of a Scheme program is defined by
@itemize{
@item{a @defterm{read} phase that processes a character stream into
an S-expression, and}
@item{an @defterm{expand} phase that processes the S-expression based
on bindings in the lexical environment, where some parsing
steps can introduce new bindings for further parsing steps.}
}
Note that parsing is defined in terms of Unicode characters; see
@secref["unicode"] for information on how a byte stream is converted
to a character stream.
@section[#:tag "reader"]{Reading Data}
@title[#:tag "mz:reader"]{Reading Data}
Scheme's reader is a recursive-descent parser that can be configured
through a @seclink["readtable"]{readtable} and various other
@ -55,7 +36,11 @@ object. Unless specified otherwise, this section describes the
reader's behavior in @scheme[read] mode, and @scheme[read-syntax] mode
does the same modulo wrapping the final result.
@subsection{Delimiters and Dispatch}
Reading is defined in terms of Unicode characters; see
@secref["unicode"] for information on how a byte stream is converted
to a character stream.
@section{Delimiters and Dispatch}
Along with @schemelink[char-whitespace?]{whitespace}, the following
characters are @defterm{delimiters}:
@ -168,7 +153,7 @@ on the next character or characters in the input stream as follows:
]
@subsection[#:tag "mz:parse-symbol"]{Reading Symbols}
@section[#:tag "mz:parse-symbol"]{Reading Symbols}
A sequence that does not start with a delimiter or @litchar{#} is
parsed as either a symbol or a number (see @secref["mz:parse-number"]),
@ -185,7 +170,7 @@ case-insensitive mode. If the reader encounters @as-index{@litchar{#cs}},
@litchar{#CS}, @litchar{#Cs}, or @litchar{#cS}, then recursively reads
the following datum in case-sensitive mode.
@reader-examples[
@reader-examples[#:symbols? #f
"Apple"
"Ap#ple"
"Ap ple"
@ -198,7 +183,7 @@ the following datum in case-sensitive mode.
"#%Apple"
]
@subsection[#:tag "mz:parse-number"]{Reading Numbers}
@section[#:tag "mz:parse-number"]{Reading Numbers}
@index['("numbers" "parsing")]{A} sequence that does not start with a
delimiter is parsed as a number when it matches the following grammar
@ -286,14 +271,14 @@ with any other mark, double-precision IEEE floating point is used.
"#b101"
]
@subsection[#:tag "mz:parse-boolean"]{Reading Booleans}
@section[#:tag "mz:parse-boolean"]{Reading Booleans}
A @as-index{@litchar{#t}} or @as-index{@litchar{#T}} is the complete
input syntax for the boolean constant true, and
@as-index{@litchar{#f}} or @as-index{@litchar{#F}} is the complete
input syntax for the boolean constant false.
@subsection[#:tag "mz:parse-pair"]{Reading Pairs and Lists}
@section[#:tag "mz:parse-pair"]{Reading Pairs and Lists}
When the reader encounters a @as-index{@litchar{(}},
@as-index{@litchar["["]}, or @as-index{@litchar["{"]}, it starts
@ -361,7 +346,7 @@ If the @scheme[read-square-bracket-as-paren] parameter is set to
then when then reader encounters @litchar["{"] and @litchar["}"], the
@exnraise{exn:fail:read}.
@subsection[#:tag "mz:parse-string"]{Reading Strings}
@section[#:tag "mz:parse-string"]{Reading Strings}
@index['("strings" "parsing")]{When} the reader encouters
@as-index{@litchar{"}}, it begins parsing characters to form a string. The
@ -460,7 +445,7 @@ encountered before a terminating line, the @exnraise[exn:fail:read].
"#\"Apple\""
]
@subsection[#:tag "mz:parse-quote"]{Reading Quotes}
@section[#:tag "mz:parse-quote"]{Reading Quotes}
When the reader enounters @as-index{@litchar{'}}, then it recursively
reads one datum, and it forms a new list containing the symbol
@ -483,10 +468,10 @@ way. Longer prefixes take precedence over short ones:
@reader-examples
[
"'apple"
"`(1 ,(+ 2 3))"
"`(1 ,2)"
]
@subsection[#:tag "mz:parse-comment"]{Reading Comments}
@section[#:tag "mz:parse-comment"]{Reading Comments}
A @as-index{@litchar{;}} starts a line comment. When the reader
encounters @litchar{;}, then it skips past all characters until the
@ -517,7 +502,7 @@ normally appears at the beginning of a Unix script file.
"#! /bin/sh"
]
@subsection[#:tag "mz:parse-vector"]{Reading Vectors}
@section[#:tag "mz:parse-vector"]{Reading Vectors}
When the reader encounters a @litchar{#(}, @litchar{#[}, or
@litchar["#{"], it starts parsing a vector; see @secref["vectors"] for
@ -547,7 +532,7 @@ vector's elements are also wraped as syntax objects.
"#3()"
]
@subsection[#:tag "mz:parse-hashtable"]{Reading Hash Tables}
@section[#:tag "mz:parse-hashtable"]{Reading Hash Tables}
A @litchar{#hash} starts an immutable hash-table constant with key
matching based on @scheme[equal?]. The characters after @litchar{hash}
@ -568,6 +553,7 @@ In either case, the table is constructed by adding each mapping to the
@reader-examples
[
#:example-note @elem{, where @scheme[make-...] stands for @scheme[make-immutable-hash-table]}
"#hash()"
"#hasheq()"
"#hash((\"a\" . 5))"
@ -575,7 +561,7 @@ In either case, the table is constructed by adding each mapping to the
"#hasheq((a . 5) (a . 7))"
]
@subsection[#:tag "mz:parse-box"]{Reading Boxes}
@section[#:tag "mz:parse-box"]{Reading Boxes}
When the reader encounters a @litchar{#&}, it starts parsing a box;
see @secref["boxes"] for information on boxes. The content of the box
@ -590,14 +576,14 @@ content is also wraped as a syntax object.
"#&17"
]
@subsection[#:tag "mz:parse-character"]{Reading Characters}
@section[#:tag "mz:parse-character"]{Reading Characters}
A @litchar["#\\"] starts a character constant, which has one of the
following forms:
@itemize{
@item{ @litchar["#\\nul"] or @litchar["#\null"]: NUL (ASCII 0)@nonalpha[]}
@item{ @litchar["#\\nul"] or @litchar["#\\null"]: NUL (ASCII 0)@nonalpha[]}
@item{ @litchar["#\\backspace"]: backspace (ASCII 8)@nonalpha[]}
@item{ @litchar["#\\tab"]: tab (ASCII 9)@nonalpha[]}
@item{ @litchar["#\\newline"] or @litchar["#\\linefeed"]: linefeed (ASCII 10)@nonalpha[]}
@ -639,7 +625,7 @@ following forms:
"#\\\u3BB"
]
@subsection[#:tag "mz:parse-keyword"]{Reading Keywords}
@section[#:tag "mz:parse-keyword"]{Reading Keywords}
A @litchar{#:} starts a keyword. The parsing of a keyword after the
@litchar{#:} is the same as for a symbol, including case-folding in
@ -652,7 +638,7 @@ never parsed as a number.
"#:1"
]
@subsection[#:tag "mz:parse-regexp"]{Reading Regular Expressions}
@section[#:tag "mz:parse-regexp"]{Reading Regular Expressions}
A @litchar{#rx} or @litchar{#px} starts a regular expression. The
characters immediately after @litchar{#rx} or @litchar{#px} must parse
@ -671,7 +657,7 @@ constructed by @scheme[byte-pregexp].
"#px#\"[\\\\s]*\""
]
@subsection[#:tag "mz:parse-graph"]{Reading Graph Structure}
@section[#:tag "mz:parse-graph"]{Reading Graph Structure}
A @graph-defn[] tags the following datum for reference via
@graph-ref[], which allows the reader to produce a datum that
@ -697,7 +683,7 @@ neither defines nor uses graph tags for other top-level forms.
"#0=(1 . #0#)"
]
@subsection[#:tag "mz:parse-reader"]{Reading via an External Reader}
@section[#:tag "mz:parse-reader"]{Reading via an External Reader}
When the reader encounters @litchar{#reader}, then it loads an
external reader procedure and applies it to the current input stream.

View File

@ -14,80 +14,92 @@
metavar
cilitchar)
(define (as-flow i) (make-flow (list (make-paragraph (if (list? i)
i
(list i))))))
(define (as-flow i) (make-flow (list (if (flow-element? i)
i
(make-paragraph (if (list? i)
i
(list i)))))))
(define spacer (hspace 1))
(define (reader-examples . strs)
(define/kw (reader-examples #:key
[symbols? #t]
[example-note ""]
#:body strs)
(make-table
#f
(cons
(list (as-flow "Examples:")
(as-flow "")
(as-flow ""))
(map (lambda (s)
(list (as-flow (list spacer
(litchar s)))
(as-flow (list spacer
"reads equal to"
spacer))
(as-flow (let ([v (read (open-input-string s))])
(cond
[(eof-object? v)
(make-element 'italic '("nothing"))]
[(string? v)
(make-element "schemevalue"
(list (schemefont
(regexp-replace* #rx"[\\]\""
(regexp-replace*
#rx"[\\][\\]"
(format "~s" v)
"\\\\x5C")
"\\\\x22"))))]
[else
(let ([e (let loop ([v v])
(cond
[(memq v '(quasiquote unquote +)) `',v]
[(symbol? v) `(string->symbol ,(format "~a" v))]
[(number? v)
(let loop ([v v])
(if (inexact? v)
`(inexact->exact ,(loop (inexact->exact v)))
(cond
[(integer? v) v]
[(real? v) `(/ ,(numerator v)
,(denominator v))]
[(complex? v) `(make-complex ,(loop (real-part v))
,(loop (imag-part v)))])))]
[(list? v) `(list ,@(map loop v))]
[(vector? v) `(vector ,@(map loop (vector->list v)))]
[(box? v) `(box ,(loop (unbox v)))]
[(and (pair? v)
(eq? v (cdr v))
(eq? 1 (car v)))
#`(let ([v (cons 1 #f)]) (set-cdr! v v) v)]
[(pair? v) `(cons ,(loop (car v)) ,(loop (cdr v)))]
[(bytes? v) `(bytes ,@(map loop (bytes->list v)))]
[(char? v) `(integer->char ,(char->integer v))]
[(keyword? v) `(string->keyword ,(format "~a" v))]
[(or (regexp? v)
(byte-regexp? v))
`(,(cond
[(pregexp? v) 'pregexp]
[(byte-pregexp? v) 'byte-pregexp]
[(byte-regexp? v) 'byte-regexp]
[else 'regexp])
,(object-name v))]
[(hash-table? v)
`(make-immutable-hash-table (quote ,(hash-table-map v cons))
,@(if (hash-table? v 'equal)
'('equal)
'()))]
[else v]))])
(to-element (syntax-ize e 0)))])))))
strs))))
(list
(list (as-flow (list "Examples" example-note ":")))
(list (make-flow
(list
(make-table
#f
(map (lambda (s)
(list (as-flow (list spacer
(litchar s)))
(as-flow (list spacer
"reads equal to"
spacer))
(as-flow (let ([v (read (open-input-string s))])
(cond
[(eof-object? v)
(make-element 'italic '("nothing"))]
[(string? v)
(make-element "schemevalue"
(list (schemefont
(regexp-replace* #rx"[\\]\""
(regexp-replace*
#rx"[\\][\\]"
(format "~s" v)
"\\\\x5C")
"\\\\x22"))))]
[else
(let ([e (let loop ([v v])
(cond
[(memq v '(quasiquote unquote +)) `',v]
[(symbol? v) (if symbols?
`(quote ,v)
`(string->symbol ,(format "~a" v)))]
[(number? v)
(let loop ([v v])
(if (inexact? v)
`(inexact->exact ,(loop (inexact->exact v)))
(cond
[(integer? v) v]
[(real? v) `(/ ,(numerator v)
,(denominator v))]
[(complex? v) `(make-complex ,(loop (real-part v))
,(loop (imag-part v)))])))]
[(list? v) `(list ,@(map loop v))]
[(vector? v) `(vector ,@(map loop (vector->list v)))]
[(box? v) `(box ,(loop (unbox v)))]
[(and (pair? v)
(eq? v (cdr v))
(eq? 1 (car v)))
(schemeblock0 (let ([v (cons 1 #f)])
(set-cdr! v v) v))]
[(pair? v) `(cons ,(loop (car v)) ,(loop (cdr v)))]
[(bytes? v) `(bytes ,@(map loop (bytes->list v)))]
[(char? v) `(integer->char ,(char->integer v))]
[(keyword? v) `(string->keyword ,(format "~a" v))]
[(or (regexp? v)
(byte-regexp? v))
`(,(cond
[(pregexp? v) 'pregexp]
[(byte-pregexp? v) 'byte-pregexp]
[(byte-regexp? v) 'byte-regexp]
[else 'regexp])
,(object-name v))]
[(hash-table? v)
`(make-... (quote ,(hash-table-map v cons))
,@(if (hash-table? v 'equal)
'('equal)
'()))]
[else v]))])
(if (flow-element? e)
e
(to-element (syntax-ize e 0))))])))))
strs))))))))
(define (read-quote-table . l)
(make-table

View File

@ -5,7 +5,8 @@
@table-of-contents[]
@include-section["read.scrbl"]
@include-section["data.scrbl"]
@include-section["syntax.scrbl"]
@include-section["read.scrbl"]
@index-section["mzscheme-index"]

View File

@ -0,0 +1,221 @@
#reader(lib "docreader.ss" "scribble")
@require["mz.ss"]
@title{Syntax}
The syntax of a Scheme program is defined by
@itemize{
@item{a @defterm{read} phase that processes a character stream into a
Scheme value, especially one composed of pairs and symbols,
and}
@item{an @defterm{expand} phase that processes the value to finish
parsing the code.}
}
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.
Expansion recursively processes a syntax-wrapped datum; for details,
see @secref["mz:expansion"]. Ultimately, expansion leads to the
synactic forms described in this section.
A syntactic form is described by a BNF-like notation that describes a
combination of (syntax-wrapped) pairs, symbols, and other data (not a
sequence of characters). In this notation, @scheme[...] indicates zero
or more repetitions of the preceding datum, @scheme[...+] indicates
one or more repetitions, and @scheme[?] means zero or one
instance. Italic sequences of characters play the role of
non-terminals. In particular:
@itemize{
@item{A sequence that ends in @scheme[_id] refers to a syntax-wrapped
symbol.}
@item{A sequence that ends in @scheme[_keyword] refers to a
syntax-wrapped keyword.}
@item{A sequence that end with @scheme[_expr] refers to a sub-form
that is expanded as an expression.}
}
@;------------------------------------------------------------------------
@section{Variable Reference}
@defform/none[id]{
A reference to a module-level or local binding, when @scheme[id] is
not bound as a transformer (see @secref["mz:expansion"]). At run-time,
the reference evaluates to the value in the location associated with
the binding.
When the expander encounters an @scheme[id] that is not bound by a
module or local binding, it converts the expression to @scheme[(#%top
. id)].}
@defform[(#%top . id)]{
A reference to a top-level definition that could bind @scheme[id],
even if @scheme[id] has a local binding in its context. Such
references are disallowed anywhere within a @scheme[module] form.}
@;------------------------------------------------------------------------
@section{Procedure Application}
@defform/none[(proc-expr arg ...)]{
A procedure application, normally, when @scheme[proc-expr] is not an
identifier that has a transformer binding (see
@secref["mz:expansion"]).
More precisely, the expander converts this form to @scheme[(#,
@schemeidfont{#%app} proc-expr arg ...)] using the lexical
context for @schemeidfont{#%app} that is associated with the original
form (i.e., the pair that combines @scheme[proc-expr] and its
arguments). Typically, the lexical context of the pair indicates the
procedure-application @scheme[#%app] that is described next.}
@defform[(#%app proc-expr arg ...)]{
A procedure application. Each @scheme[arg] is one of the following:
@specsubform[arg-expr]{The resulting value is a non-keyword
argument.}
@specsubform[(code:line keyword arg-expr)]{The resulting value is a
keyword argument using @scheme[keyword]. Each
@scheme[keyword] in the application must be distinct.}
The @scheme[proc-expr] and @scheme[_arg-expr]s are evaluated in order,
left to right. If the result of @scheme[proc-expr] is a procedure that
accepts as many arguments as non-@scheme[_keyword]
@scheme[_arg-expr]s, if it accepts arguments for all of the
e@scheme[_keyword]s in the application, and if all required
keyword-based arguments are represented among the @scheme[_keyword]s
in the application, then the procedure is called with the values of
the @scheme[arg-expr]s. Otherwise, the @exnraise[exn:fail:contract].
The continuation of the procedure call is the same as the continuation
of the application expression, so the result(s) of the application
expression is(are) the result(s) of the procedure.
The relative order of @scheme[_keyword]-based arguments matters only
for the order of @scheme[_arg-expr] evaluations; the arguments are
regonized by the applied procedure based on the @scheme[_keyword], and
not their positions. The other @scheme[_arg-expr] values, in contrast,
are recognized by the applied procedure according to their order in
the application form.}
@;------------------------------------------------------------------------
@section{Procedure Expression: @scheme[lambda] and @scheme[case-lambda]}
@defform[(lambda formals* body-expr ...+)]{
An expression that procedures a procedure. The @scheme[formals*]
determines the number of arguments that the procedure accepts. It is
either a simple @scheme[_formals], or one of the extended forms.
A simple @scheme[_formals] has one of the following three forms:
@specsubform[(id ... )]{ The procedure accepts as many non-keyword
argument values as the number of @scheme[id]s. Each @scheme[id]
is associated with an argument value by position.}
@specsubform[(id ...+ . rest-id)]{ The procedure accepts any number of
non-keyword arguments greater or equal to the number of
@scheme[id]s. When the procedure is applied, the @scheme[id]s
are associated with argument values by position, and all
leftover arguments are placed into a list that is associated to
@scheme[rest-id].}
@specsubform[rest-id]{ The procedure accepts any number of non-keyword
arguments. All arguments are placed into a list that is
associated with @scheme[rest-id].}
In addition to the form of a @scheme[_formals], a @scheme[formals*]
can be a sequence of @scheme[_formal*]s optionally ending with a
@scheme[rest-id]:
@specsubform[(formal* ...)]{ Each @scheme[formal*] has the following
four forms:
@specsubform[id]{Adds one to both the minimum and maximum
number of non-keyword arguments accepted by the procedure. The
@scheme[id] is associated with an actual argument by
position.}
@specsubform[[id default-expr]]{Adds one to the maximum number
of non-keyword arguments accepted by the procedure. The
@scheme[id] is associated with an actual argument by position,
and if no such argument is provided, the @scheme[default-expr]
is evaluated to produce a value associated with @scheme[id].
No @scheme[formal*] with a @scheme[default-expr] can appear
before an @scheme[id] without a @scheme[default-expr] and
without a @scheme[keyword].}
@specsubform[(code:line keyword id)]{The procedure requires a
keyword-based argument using @scheme[keyword]. The @scheme[id]
is associated with a keyword-based actual argument using
@scheme[keyword].}
@specsubform[(code:line keyword [id default-expr])]{The
procedure accepts a keyword-based using @scheme[keyword]. The
@scheme[id] is associated with a keyword-based actual argument
using @scheme[keyword], if supplied in an application;
otherwise, the @scheme[default-expr] is evaluated to obtain a
value to associate with @scheme[id].}
The position of a @scheme[_keyword] @scheme[formal*] in
@scheme[formals*] does not matter, but each specified
@scheme[_keyword] must be distinct.}
@specsubform[(formal* ...+ . rest-id)]{ Like the previous case, but
the procedure accepts any number of non-keyword arguments
beyond its minimum number of arguments. When more arguments are
provided than non-@scheme[_keyword] arguments among the @scheme[formal*]s,
the extra arguments are placed into a list that is associated to
@scheme[rest-id].}
The @scheme[formals*] identifiers are bound in the
@scheme[body-expr]s. When the procedure is applied, a new location is
created for each identifier, and the location is filled with the
associated argument value.
If any identifier appears in @scheme[body-expr]s that is not one of
the identifiers in @scheme[formals*], then it refers to the same
location that it would if it appears in place of the @scheme[lambda]
expression. (In other words, variable reference is lexically scoped.)
When multiple identifiers appear in a @scheme[formals*], they must be
distinct according to @scheme[bound-identifier=?].
If the procedure procedure by @scheme[lambda] is applied to fewer or
more arguments than it accepts, the @exnraise[exn:fail:contract]. If
@scheme[formals*] includes @scheme[keyword]s and an application
includes too few arguments before the keyword section, the same
keyword in multiple odd positions of the keyword section, or a keyword
that is not among the @scheme[formals*] @scheme[keyword]s in an odd
position of the keyword section, then the
@exnraise[exn:fail:contract].}
@defform[(case-lambda [formals body-expr ...+] ...)]{
An expression that procedure. Each @scheme[[forms body-expr ...+]]
clause is analogous to a single @scheme[lambda] procedure; applying
the @scheme[case-lambda]-generated procedure is the same as applying a
procedure that corresponds to one of the clauses---the first procedure
that accepts the given number of arguments. If no corresponding
procedure accepts the given number of arguments, the
@exnraise[exn:fail:contract].
Note that a @scheme[case-lambda] clause supports only
@scheme[formals], not the more general @scheme[_formals*] of
@scheme[lambda]. That is, @scheme[case-lambda] does not directly
support keyword and optional arguments for an inidvidual clause.}

View File

@ -159,112 +159,103 @@ in a form definition.}
@; ------------------------------------------------------------------------
@section{Definition Reference}
@defform[(defproc (identifier arg-spec ...) result-contract-expr-datum pre-flow ...)]{Produces
a sequence of flow elements (encaptured in a @scheme[splice]) to
document a procedure named @scheme[identifier]. The
@scheme[identifier] is registered so that @scheme[scheme]-typeset uses
@defform[(defproc (id arg-spec ...)
result-contract-expr-datum
pre-flow ...)]{
Produces a sequence of flow elements (encaptured in a @scheme[splice])
to document a procedure named @scheme[id]. The
@scheme[id] is registered so that @scheme[scheme]-typeset uses
of the identifier are hyperlinked to this documentation.
Each @scheme[arg-spec] must have one of the following forms:
@itemize{
@item{@specsubform/inline[(arg-identifier contract-expr-datum)]{---
an argument whose contract is specified by
@specsubform[(arg-id contract-expr-datum)]{
An argument whose contract is specified by
@scheme[contract-expr-datum] which is typeset via
@scheme[scheme].}}
@scheme[scheme].}
@item{@specsubform/inline[(arg-identifier contract-expr-datum
default-expr)]{ --- like the previous case, but with a default
value. All arguments with a default value must be grouped
together, but they can be in the middle of required
arguments.}}
@specsubform[(arg-id contract-expr-datum default-expr)]{
Like the previous case, but with a default value. All arguments
with a default value must be grouped together, but they can be
in the middle of required arguments.}
@item{@specsubform/inline[(keyword arg-identifier
contract-expr-datum)]{ --- like the first case, but for a
keyword-based argument.}}
@specsubform[(keyword arg-id contract-expr-datum)]{
Like the first case, but for a keyword-based argument.}
@item{@specsubform/inline[(keyword arg-identifier contract-expr-datum
default-expr)]{ --- like the previous case, but with a default
value.}}
@specsubform[(keyword arg-id contract-expr-datum default-expr)]{
Like the previous case, but with a default
value.}
@item{@scheme[...0] --- any number of the preceding argument
(normally at the end)}
@specsubform[#, @schemeidfont{...0}]{ Any number of the preceding argument
(normally at the end).}
@item{@scheme[...1] --- one or more of the preceding argument
(normally at the end)}
}
@specsubform[#, @schemeidfont{...1}]{One or more of the preceding argument
(normally at the end).}
The @scheme[result-contract-expr-datum] is typeset via
@scheme[scheme], and it represents a contract on the procedure's
result.
The @scheme[pre-flow]s list is parsed as a flow that documents the
procedure. In this description, references to @svar[arg-identifier]s
procedure. In this description, references to @svar[arg-id]s
are typeset as procedure arguments.
The typesetting of all data before the @scheme[pre-flow]s ignores the
source layout.}
@defform[(defproc* (((identifier arg-spec ...) result-contract-expr-datum) ...) pre-flow ...)]{Like
@scheme[defproc], but for multiple cases with the same @scheme[identifier].
}
@defform[(defproc* ([(id arg-spec ...)
result-contract-expr-datum] ...)
pre-flow ...)]{
Like @scheme[defproc], but for multiple cases with the same
@scheme[id]. }
@defform[(defform (identifier . datum) pre-flow ...)]{Produces a
@defform[(defform (id . datum) pre-flow ...)]{Produces a
a sequence of flow elements (encaptured in a @scheme[splice]) to
document a syntaic form named by @scheme[identifier]. The
@scheme[identifier] is registered so that @scheme[scheme]-typeset uses
document a syntatic form named by @scheme[id]. The
@scheme[id] is registered so that @scheme[scheme]-typeset uses
of the identifier are hyperlinked to this documentation.
The @scheme[pre-flow]s list is parsed as a flow that documents the
procedure. In this description, a reference to any identifier in
@scheme[datum] is typeset as a sub-form non-terminal.
The typesetting of @scheme[(identifier . datum)] preserves the source
The typesetting of @scheme[(id . datum)] preserves the source
layout, like @scheme[scheme], and unlike @scheme[defproc].}
@defform[(specsubform/inline datum pre-flow ...)]{Similar to
@defform[(specsubform datum pre-flow ...)]{Similar to
@scheme[defform], but without any specific identifier being defined,
without the output format that highlights a definition, and with
@scheme[datum] as an element rather than a table. This form is
intended for use when refining the syntax of a non-terminal used in a
@scheme[defform], @scheme[specsubform], or other
@scheme[specsubform/inline]. For example, it is used in the
documentation for @scheme[defproc] in the itemization of possible
shapes for @svar[arg-spec].
and the table and flow are typeset indented. This form is intended for
use when refining the syntax of a non-terminal used in a
@scheme[defform] or other @scheme[specsubform]. For example, it is
used in the documentation for @scheme[defproc] in the itemization of
possible shapes for @svar[arg-spec].
The @scheme[pre-flow]s list is parsed as a flow that documents the
procedure. In this description, a reference to any identifier in
@scheme[datum] is typeset as a sub-form non-terminal.}
@defform[(specsubform datum pre-flow ...)]{Like
@scheme[specsubform/inline], but the @scheme[datum] is typeset in the
resulting flow as a table instead of an element.}
@defform[(defthing identifier contract-expr-datum pre-flow ...)]{Like
@defform[(defthing id contract-expr-datum pre-flow ...)]{Like
@scheme[defproc], but for a non-procedure binding.}
@defform[(defstruct struct-name ([field-name contract-expr-datum] ...) pre-flow ...)]{Similar
to @scheme[defform], but for a structure definition.
@defform[(defstruct struct-name ([field-name contract-expr-datum] ...)
pre-flow ...)]{
Similar to @scheme[defform], but for a structure definition.
The @scheme[struct-name] can be either of the following:
@itemize{
@specsubform[id]{A structure type with no
specified supertype.}
@item{@specsubform/inline[identifier]{--- a structure type with no
specified supertype.}}
@item{@specsubform/inline[(identifier super-identifier)]{ --- a structure
type with indicated supertype.}}
}}
@specsubform[(id super-id)]{A type with indicated supertype.}
}
@; ------------------------------------------------------------------------
@section{Various String Forms}