finish mz docs

svn: r8123
This commit is contained in:
Matthew Flatt 2007-12-26 02:58:13 +00:00
parent 36ca820232
commit 5c76cb507e
14 changed files with 357 additions and 67 deletions

View File

@ -8,8 +8,8 @@ The _compiler.ss_ library defines the following functions (plus a few
signatures). Options that control the compiler are documented in the signatures). Options that control the compiler are documented in the
next section. next section.
Single-file extension compilation Extension compilation
--------------------------------- ---------------------
> ((compile-extensions expr) scheme-file-list dest-dir) > ((compile-extensions expr) scheme-file-list dest-dir)

View File

@ -603,7 +603,10 @@
(or (null? modes) (or (null? modes)
(memq 'run modes)) (memq 'run modes))
(memq 'syntax modes) (memq 'syntax modes)
(memq 'label modes))]) (memq 'label modes))]
[(ok-context?) (lambda (id id=?)
(id=? id
(datum->syntax mp (syntax-e id))))])
(when (or (null? modes) (when (or (null? modes)
(memq 'run modes)) (memq 'run modes))
(unless ids (unless ids
@ -626,25 +629,30 @@
"no corresponding for-label require" "no corresponding for-label require"
stx stx
mp))) mp)))
(filter
values
(append (append
(map (lambda (id) (map (lambda (id)
(make-export id (syntax-e id) 'syntax #f stx)) (and (ok-context? id free-transformer-identifier=?)
(make-export id (syntax-e id) 'syntax #f stx)))
(if (or (null? modes) (if (or (null? modes)
(memq 'syntax modes)) (memq 'syntax modes))
(or stx-ids null) (or stx-ids null)
null)) null))
(map (lambda (id) (map (lambda (id)
(make-export id (syntax-e id) 'label #f stx)) (and (ok-context? id free-label-identifier=?)
(make-export id (syntax-e id) 'label #f stx)))
(if (or (null? modes) (if (or (null? modes)
(memq 'label modes)) (memq 'label modes))
(or label-ids null) (or label-ids null)
null)) null))
(map (lambda (id) (map (lambda (id)
(make-export id (syntax-e id) 'run #f stx)) (and (ok-context? id free-identifier=?)
(make-export id (syntax-e id) 'run #f stx)))
(if (or (null? modes) (if (or (null? modes)
(memq 'run modes)) (memq 'run modes))
ids ids
null))))) null))))))
(syntax->list #'(mp ...))))])))) (syntax->list #'(mp ...))))]))))
(define-syntax rename-out (define-syntax rename-out

View File

@ -440,7 +440,7 @@
(provide declare-exporting (provide declare-exporting
deftogether deftogether
defproc defproc* defstruct defthing defthing* defparam defboolparam defproc defproc* defstruct defthing defthing* defparam defparam* defboolparam
defform defform* defform/subs defform*/subs defform/none defform defform* defform/subs defform*/subs defform/none
defidform defidform
specform specform/subs specform specform/subs
@ -688,6 +688,10 @@
(syntax-rules () (syntax-rules ()
[(_ id arg contract desc ...) [(_ id arg contract desc ...)
(defproc* ([(id) contract] [(id [arg contract]) void?]) desc ...)])) (defproc* ([(id) contract] [(id [arg contract]) void?]) desc ...)]))
(define-syntax defparam*
(syntax-rules ()
[(_ id arg in-contract out-contract desc ...)
(defproc* ([(id) out-contract] [(id [arg in-contract]) void?]) desc ...)]))
(define-syntax defboolparam (define-syntax defboolparam
(syntax-rules () (syntax-rules ()
[(_ id arg desc ...) [(_ id arg desc ...)

View File

@ -55,7 +55,12 @@ it is sent to the @tech{evaluation handler}:
@scheme[namespace-syntax-introduce] is applied to the entire @scheme[namespace-syntax-introduce] is applied to the entire
syntax object.} syntax object.}
}} }
For interactive evaluation in the style of
@scheme[read-eval-print-loop] and @scheme[load], wrap each expression
with @schemeidfont{#%top-interaction}, which is normally bound to
@scheme[#%top-interaction], before passing it to @scheme[eval].}
@defproc[(eval-syntax [stx syntax?] @defproc[(eval-syntax [stx syntax?]
@ -89,10 +94,11 @@ port, unless the path has a @scheme[".zo"] suffix. It also
@scheme[#t], then @scheme[read-on-demand-source] is effectively set to @scheme[#t], then @scheme[read-on-demand-source] is effectively set to
the @tech{cleanse}d, absolute form of @scheme[path] during the the @tech{cleanse}d, absolute form of @scheme[path] during the
@scheme[read-syntax] call. After reading a single form, the form is @scheme[read-syntax] call. After reading a single form, the form is
passed to the current evaluation handler, wrapping the evaluation in a passed to the current @tech{evaluation handler}, wrapping the
continuation prompt (see @scheme[call-with-continuation-prompt]) for evaluation in a continuation prompt (see
the default continuation prompt tag with handler that propagates the @scheme[call-with-continuation-prompt]) for the default continuation
abort to the continuation of the @scheme[load] call. prompt tag with handler that propagates the abort to the continuation
of the @scheme[load] call.
If the second argument to the load handler is a symbol, then: If the second argument to the load handler is a symbol, then:
@ -130,6 +136,12 @@ If the second argument to the load handler is a symbol, then:
} }
If the second argument to the load handler is @scheme[#f], then each
expression read from the file is wrapped with
@schemeidfont{#%top-interaction}, which is normally bound to
@scheme[#%top-interaction], before passing it to the @tech{evaluation
handler}.
The return value from the default @tech{load handler} is the value of The return value from the default @tech{load handler} is the value of
the last form from the loaded file, or @|void-const| if the file the last form from the loaded file, or @|void-const| if the file
contains no forms. If the given path is a relative path, then it is contains no forms. If the given path is a relative path, then it is
@ -248,7 +260,7 @@ immediately expanded (see @secref["pathutils"]) and converted to a
path. (The directory need not exist.)} path. (The directory need not exist.)}
@defparam[use-compiled-file-paths paths (listof path?)]{ @defparam*[use-compiled-file-paths paths (listof path-string?) (listof path?)]{
A list of relative paths, which defaults to @scheme[(list A list of relative paths, which defaults to @scheme[(list
(string->path "compiled"))]. It is used by the @tech{compiled-load (string->path "compiled"))]. It is used by the @tech{compiled-load
@ -257,12 +269,14 @@ handler} (see @scheme[current-load/use-compiled]).}
@defproc[(read-eval-print-loop) any]{ @defproc[(read-eval-print-loop) any]{
Starts a new REPL using the current input, output, and error Starts a new @deftech{REPL} using the current input, output, and error
ports. The REPL wraps each evaluation with a continuation prompt using ports. The REPL wraps each expression to evaluate with
the default continuation prompt tag and prompt handler (see @schemeidfont{#%top-interaction}, which is normally bound to
@scheme[call-with-continuation-prompt]). The REPL also wraps the read @scheme[#%top-interaction], and it wraps each evaluation with a
and print operations with a prompt for the default tag whose handler continuation prompt using the default continuation prompt tag and
ignores abort arguments and continues the loop. The prompt handler (see @scheme[call-with-continuation-prompt]). The REPL
also wraps the read and print operations with a prompt for the default
tag whose handler ignores abort arguments and continues the loop. The
@scheme[read-eval-print-loop] procedure does not return until @scheme[read-eval-print-loop] procedure does not return until
@scheme[eof] is read, at which point it returns @|void-const|. @scheme[eof] is read, at which point it returns @|void-const|.

View File

@ -315,3 +315,33 @@ property is not associated with a procedure structure type.
(pairs 1 2 3 4) (pairs 1 2 3 4)
(pairs 5)]} (pairs 5)]}
@; ----------------------------------------------------------------------
@section{Reflecting on Primitives}
A @idefterm{primitive procedure} is a built-in procedure that is
implemented in low-level language. Not all procedures of
@schememodname[scheme/base] are primitives, but many are. The
distinction is mainly useful to other low-level code.
@defproc[(primitive? [v any/c]) boolean?]{
Returns @scheme[#t] if @scheme[v] is a primitive procedure,
@scheme[#f] otherwise.}
@defproc[(primitive-closure? [v any/c]) boolean]{
Returns @scheme[#t] if @scheme[v] is internally implemented as a
primitive closure rather than a simple primitive procedure,
@scheme[#f] otherwise.}
@defproc[(primitive-result-arity [prim primitive?]) procedure-arity?]{
Returns the arity of the result of the primitive procedure
@scheme[prim] (as opposed to the procedure's input arity as returned
by @scheme[arity]). For most primitives, this procedure returns
@scheme[1], since most primitives return a single value when
applied.}

View File

@ -1,7 +1,7 @@
#lang scribble/doc #lang scribble/doc
@require["mz.ss"] @require["mz.ss"]
@title{Environment and Runtime Information} @title[#:tag "runtime"]{Environment and Runtime Information}
@defproc[(getenv [name string?]) (or/c string? false/c)]{ @defproc[(getenv [name string?]) (or/c string? false/c)]{
@ -121,6 +121,14 @@ Scheme starts (not including any command-line arguments that were
treated as flags for the system).} treated as flags for the system).}
@defparam[current-thread-initial-stack-size exact-positive-integer?]{
A parameter that provides a hint about how much space to reserve for a
newly created thread's local variables. The actual space used by a
computation is affected by just-in-time (JIT) compilation, but it is
otherwise platform-independent.}
@defproc[(vector-set-performance-stats! [results (and/c vector? @defproc[(vector-set-performance-stats! [results (and/c vector?
(not/c immutable?))] (not/c immutable?))]
[thd (or/c thread? false/c) #f]) [thd (or/c thread? false/c) #f])

View File

@ -163,7 +163,8 @@ transformer expression instead of a run-time expression.}
[stop-ids (or/c (listof identifier?) false/c)] [stop-ids (or/c (listof identifier?) false/c)]
[intdef-ctx (or/c internal-definition-context? [intdef-ctx (or/c internal-definition-context?
false/c) false/c)
#f]) #f]
[lift-ctx any/c (gensym 'lifts)])
syntax?]{ syntax?]{
Like @scheme[local-expand], but if Like @scheme[local-expand], but if
@ -171,8 +172,12 @@ Like @scheme[local-expand], but if
of @scheme[stx], the result is a syntax object that represents a of @scheme[stx], the result is a syntax object that represents a
@scheme[begin] expression; lifted expression appear with their @scheme[begin] expression; lifted expression appear with their
identifiers in @scheme[define-values] forms, and the expansion of identifiers in @scheme[define-values] forms, and the expansion of
@scheme[stx] is the last expression in the @scheme[begin]. The lifted @scheme[stx] is the last expression in the @scheme[begin]. The
expressions are not expanded.} @scheme[lift-ctx] value is reported by
@scheme[syntax-local-lift-context] during local expansion. The lifted
expressions are not expanded, but instead left as provided in the
@scheme[begin] form.}
@defproc[(local-transformer-expand/capture-lifts [stx syntax?] @defproc[(local-transformer-expand/capture-lifts [stx syntax?]
[context-v (or/c (one-of 'expression 'top-level 'module [context-v (or/c (one-of 'expression 'top-level 'module
@ -285,6 +290,21 @@ Other syntactic forms can capture lifts by using
@transform-time[]} @transform-time[]}
@defproc[(syntax-local-lift-context)
any/c]{
Returns a value that represents the target for expressions lifted via
@scheme[syntax-local-lift-expression]. That is, for different
transformer calls for which this procedure returns the same value (as
determined by @scheme[eq?]), lifted expressions for the two
transformer are moved to the same place. Thus, the result is useful
for caching lift information to avoid redundant lifts.
@transform-time[]}
@defproc[(syntax-local-lift-module-end-declaration [stx syntax?]) @defproc[(syntax-local-lift-module-end-declaration [stx syntax?])
void?]{ void?]{
@ -333,6 +353,19 @@ contexts.
@transform-time[]} @transform-time[]}
@defproc[(syntax-local-module-exports [mod-path module-path?])
(values (listof symbol?) (listof symbol?) (listof symbol?))]{
Returns three lists of symbols that represent the @scheme[provide]d
bindings of the module named by @scheme[mod-path]. The first list
corresponds to the @tech{phase level} 0 exports of the module, the
second list corresponds to the @tech{phase level} -1 exports of the
module, and the last list corresponds to the @tech{label phase level}
exports of the module.
@transform-time[]}
@defproc[(syntax-local-get-shadower [id-stx identifier?]) identifier?]{ @defproc[(syntax-local-get-shadower [id-stx identifier?]) identifier?]{
Returns @scheme[id-stx] if no binding in the current expansion context Returns @scheme[id-stx] if no binding in the current expansion context
@ -444,7 +477,7 @@ import sources.}
@defproc[(make-require-transformer [proc ((syntax?) . ->* . ((listof import?) (listof import-source?)))]) @defproc[(make-require-transformer [proc ((syntax?) . ->* . ((listof import?) (listof import-source?)))])
require-transformer?]{ require-transformer?]{
Creates a require transformer (i.e., a structure with the Creates a @tech{require transformer} (i.e., a structure with the
@scheme[prop:require-transformer] property) using the given procedure @scheme[prop:require-transformer] property) using the given procedure
as the transformer.} as the transformer.}
@ -551,7 +584,7 @@ single symbol.}
. -> . (listof export?))]) . -> . (listof export?))])
provide-transformer?]{ provide-transformer?]{
Creates a provide transformer (i.e., a structure with the Creates a @deftech{provide transformer} (i.e., a structure with the
@scheme[prop:provide-transformer] property) using the given procedure @scheme[prop:provide-transformer] property) using the given procedure
as the transformer.} as the transformer.}
@ -594,3 +627,58 @@ A structure representing a single imported identifier:
exporting module.} exporting module.}
}} }}
@defproc[(syntax-local-transforming-module-provides?) boolean?]{
Returns @scheme[#t] while a provide transformer is running or while a
@schemeidfont{expand} sub-form of @scheme[#%provide] is expanded,
@scheme[#f] otherwise.}
@defproc[(syntax-local-module-defined-identifiers)
(values (listof identifier?) (listof identifier?))]{
Returns two lists of identifiers corresponding to all definitions
within the module being expanded. This information is used for
implementing @scheme[provide] sub-forms like @scheme[all-defined-out].
The first result list corresponds to @tech{phase} 0 (i.e., normal)
definitions, and the second corresponds to @tech{phase} -1 (i.e.,
for-syntax) definitions.
This procedure can be called only while
@scheme[syntax-local-transforming-module-provides?] returns
@scheme[#t].}
@defproc[(syntax-local-module-required-identifiers
[mod-path module-path?]
[normal-imports? any/c]
[syntax-imports? any/c]
[label-imports? any/c])
(values (listof identifier?)
(listof identifier?)
(listof identifier?))]{
Returns three lists of identifiers corresponding to all bindings
imported into the module being expanded using the module path
@scheme[mod-path]. This information is used for implementing
@scheme[provide] sub-forms like @scheme[all-from-out].
The first result list corresponds to @tech{phase level} 0 (i.e.,
normal) bindings, and the second list corresponds to @tech{phase
level} -1 (i.e., for-syntax) bindings, and the last list corresponds
corresponds to @tech{label phase level} (i.e., for-label) bindings.
The @scheme[normal-imports?], @scheme[syntax-imports?], and
@scheme[label-imports?] arguments determine whether each of normal,
@scheme[for-syntax], and @scheme[for-label] @scheme[require]s are
considered in building the result lists. Note that normal
@scheme[require]s can add to all three lists, while
@scheme[for-syntax] and @scheme[for-label] @scheme[require]s
contribute only to one of the latter two lists, respectively.
This procedure can be called only while
@scheme[syntax-local-transforming-module-provides?] returns
@scheme[#t].}

View File

@ -1252,7 +1252,9 @@ pre-defined forms are as follows.
@specsubform[module-path]{ Imports all exported bindings from the @specsubform[module-path]{ Imports all exported bindings from the
named module, using the export identifiers as the local identifiers. named module, using the export identifiers as the local identifiers.
(See below for information on @scheme[module-path].)} (See below for information on @scheme[module-path].) The lexical
context of the @scheme[module-path] form determines the context of
the introduced identifiers.}
@defsubform[(only-in require-spec id-maybe-renamed ...)]{ @defsubform[(only-in require-spec id-maybe-renamed ...)]{
Like @scheme[require-spec], but constrained to those exports for Like @scheme[require-spec], but constrained to those exports for
@ -1270,7 +1272,9 @@ pre-defined forms are as follows.
@defsubform[(prefix-in prefix-id require-spec)]{ Like @defsubform[(prefix-in prefix-id require-spec)]{ Like
@scheme[require-spec], but adjusting each identifier to be bound by @scheme[require-spec], but adjusting each identifier to be bound by
prefixing it with @scheme[prefix-id].} prefixing it with @scheme[prefix-id]. The lexical context of the
@scheme[prefix-id] is ignored, and instead preserved from the
identifiers before prefixing.}
@defsubform[(rename-in require-spec [orig-id bind-id] ...)]{ @defsubform[(rename-in require-spec [orig-id bind-id] ...)]{
Like @scheme[require-spec], but replacing the identifier to Like @scheme[require-spec], but replacing the identifier to
@ -1410,13 +1414,15 @@ pre-defined forms are as follows.
level} 0. The symbolic form of @scheme[id] is used as the external level} 0. The symbolic form of @scheme[id] is used as the external
name.} name.}
@defsubform[(all-defined-out)]{ Exports @defsubform[(all-defined-out)]{ Exports all identifiers that are
all identifiers that are defined at @tech{phase level} 0 or defined at @tech{phase level} 0 or @tech{phase level} 1 within the
@tech{phase level} 1 within the exporting module. The external name exporting module, and that have the same lexical context as the
for each identifier is the symbolic form of the identifier; note that @scheme[(all-defined-out)] form. The external name for each
this can lead to an illegal multiple export for a single symbolic identifier is the symbolic form of the identifier. Only identifiers
name in the case different identifier bindings have the same symbolic accessible from the lexical context of the @scheme[(all-defined-out)]
name.} form are included; that is, macro-introduced imports are not
re-exported, unless the @scheme[(all-defined-out)] form was
introduced at the same time.}
@defsubform[(all-from-out module-path ...)]{ Exports all identifiers @defsubform[(all-from-out module-path ...)]{ Exports all identifiers
that are imported into the exporting module using a that are imported into the exporting module using a
@ -1424,7 +1430,10 @@ pre-defined forms are as follows.
@secref["require"]) with no @tech{phase-level} shift. The symbolic @secref["require"]) with no @tech{phase-level} shift. The symbolic
name for export is derived from the name that is bound within the name for export is derived from the name that is bound within the
module, as opposed to the symbolic name of the export from each module, as opposed to the symbolic name of the export from each
@scheme[module-path].} @scheme[module-path]. Only identifiers accessible from the lexical
context of the @scheme[module-path] are included; that is,
macro-introduced imports are not re-exported, unless the
@scheme[module-path] was introduced at the same time.}
@defsubform[(rename-out [orig-id export-id] ...)]{ Exports each @defsubform[(rename-out [orig-id export-id] ...)]{ Exports each
@scheme[orig-id], which must be @tech{bound} within the module at @scheme[orig-id], which must be @tech{bound} within the module at
@ -1483,12 +1492,109 @@ multiple symbolic names.}
@defform[(for-template require-spec ...)]{See @scheme[require].} @defform[(for-template require-spec ...)]{See @scheme[require].}
@defform[(for-label require-spec ...)]{See @scheme[require] and @scheme[provide].} @defform[(for-label require-spec ...)]{See @scheme[require] and @scheme[provide].}
@defform[(#%require raw-require-spec ...)]{ @defform/subs[(#%require raw-require-spec ...)
([raw-require-spec phaseless-require-spec
(#,(schemeidfont "for-syntax") phaseless-spec ...)
(#,(schemeidfont "for-template") phaseless-spec ...)
(#,(schemeidfont "for-label") phaseless-spec ...)]
[phaseless-spec raw-module-path
(#,(schemeidfont "only") rw-module-path id ...)
(#,(schemeidfont "prefix") prefix-id raw-module-path)
(#,(schemeidfont "all-except") raw-module-path id ...)
(#,(schemeidfont "prefix-all-except") prefix-id
raw-module-path id ...)
(#,(schemeidfont "rename") raw-module-path local-id exported-id)]
[raw-module-path (#,(schemeidfont "quote") id)
rel-string
(#,(schemeidfont "lib") rel-string ...)
id
(#,(schemeidfont "file") string)
(#,(schemeidfont "planet") rel-string
(user-string pkg-string vers ...))])]{
A primitive import form, to which @scheme[require] The primitive import form, to which @scheme[require] expands. A
expands. @italic{To be documented...}} @scheme[raw-require-spec] is similar to a @scheme[_require-spec] in a
@scheme[require] form, except that the syntax is more constrained, not
composable, and not extensible. Also, sub-form names like
@schemeidfont{for-syntax} and @schemeidfont{lib} are recognized
symbolically, instead of via bindings.
@defform[(#%provide raw-require-spec ...)]{ Each @scheme[raw-require-spec] corresponds to the obvious
@scheme[_require-spec], but the @schemeidfont{rename} sub-form has the
identifiers in reverse order compared to @scheme[rename-in].
A primitive export form, to which @scheme[provide] expands. @italic{To be For most @scheme[raw-require-spec]s, the lexical context of the
documented...}} @scheme[raw-require-spec] determines the context of introduced
identifiers. The exception is the @schemeidfont{rename} sub-form,
where the lexical context of the @scheme[local-id] is preserved.}
@defform/subs[(#%provide raw-provide-spec ...)
([raw-provide-spec phaseless-spec
(#,(schemeidfont "for-syntax") phaseless-spec)
(#,(schemeidfont "for-label") phaseless-spec)
(#,(schemeidfont "protect") raw-provide-spec)]
[phaseless-spec id
(#,(schemeidfont "rename") local-id export-id)
(#,(schemeidfont "struct") struct-id (field-id ...))
(#,(schemeidfont "all-from") raw-module-path)
(#,(schemeidfont "all-from-except") raw-module-path id ...)
(#,(schemeidfont "all-defined"))
(#,(schemeidfont "all-defined-except") id ...)
(#,(schemeidfont "prefix-all-defined") prefix-id)
(#,(schemeidfont "prefix-all-defined-except") prefix-id id ...)
(#,(schemeidfont "protect") phaseless-spec ...)
(#,(schemeidfont "expand") (id . datum))])]{
The primitive export form, to which @scheme[provide] expands. A
@scheme[_raw-module-path] is as for @scheme[#%require]. A
@schemeidfont{protect} sub-form cannot appear within a
@scheme[protect] sub-form.
Like @scheme[#%require], the sub-form keywords for @scheme[#%provide]
are recognized symbolically, and nearly every
@scheme[raw-provide-spec] has an obvious equivalent
@scheme[_provide-spec] via @scheme[provide], with the exception of the
@schemeidfont{struct} and @schemeidfont{expand} sub-forms.
A @scheme[(#,(schemeidfont "struct") struct-id (field-id ...))]
sub-form expands to @scheme[struct-id],
@schemeidfont{make-}@scheme[struct-id],
@schemeidfont{struct:}@scheme[struct-id],
@scheme[struct-id]@schemeidfont{?},
@scheme[struct-id]@schemeidfont{-}@scheme[field-id] for each
@scheme[field-id], and
@schemeidfont{set-}@scheme[struct-id]@schemeidfont{-}@scheme[field-id]@schemeidfont{!}
for each @scheme[field-id]. The lexical context of the
@scheme[struct-id] is used for all generated identifiers.
Unlike @scheme[#%require], the @scheme[#%provide] form is
macro-extensible via an explicit @schemeidfont{expand} sub-form; the
@scheme[(id . datum)] part is locally expanded as an expression (even
though it is not actually an expression), stopping when a
@scheme[begin] form is produced; if the expansion result is
@scheme[(begin raw-provide-spec ...)], it is spliced in place of the
@schemeidfont{expand} form, otherwise a syntax error is reported. The
@schemeidfont{expand} sub-form is not normally used directly; it
provides a hook for implementing @scheme[provide] and @tech{provide
transformers}.
The @schemeidfont{all-from} and @schemeidfont{all-from-except} forms
re-export only identifiers that are accessible in lexical context of
the @schemeidfont{all-from} or @schemeidfont{all-from-except} form
itself. That is, macro-introduced imports are not re-exported, unless
the @schemeidfont{all-from} or @schemeidfont{all-from-except} form was
introduced at the same time. Similarly, @schemeidfont{all-defined} and
its variants export only definitions accessible from the lexical
context of the @scheme[phaseless-spec] form.}
@;------------------------------------------------------------------------
@section{Interaction Wrapper: @scheme[#%top-interaction]}
@defform[(#%top-interaction . form)]{
Expands to simply @scheme[form]. The @scheme[#%top-interaction] form
is similar to @scheme[#%app] and @scheme[#%module-begin], in that it
provides a hook to control interactive evaluation through
@scheme[load] (more precisely, the default @tech{load handler}) or
@scheme[read-eval-print-loop].}

View File

@ -187,6 +187,20 @@ A parameter that controls printing values in an alternate syntax. See
@|HonuManual| for more information.} @|HonuManual| for more information.}
@defparam*[current-write-relative-directory path
(or/c (and/c path-string? complete-path?) false/c)
(or/c (and/c path? complete-path?) false/c)]{
A parameter that is used when writing compiled code that contains
pathname literals, including source-location pathnames for procedure
names. When not @scheme[#f], paths that syntactically extend the
parameter's value are converted to relative paths; when the resulting
compiled code is read, relative paths are converted back to complete
paths using the @scheme[current-load-relative-directory] parameter (if
it is not @scheme[#f], otherwise the path is left relative).}
@defproc*[([(port-write-handler [out output-port?]) (any/c output-port? . -> . any)] @defproc*[([(port-write-handler [out output-port?]) (any/c output-port? . -> . any)]
[(port-write-handler [in input-port?] [(port-write-handler [in input-port?]
[proc (any/c output-port? . -> . any)]) [proc (any/c output-port? . -> . any)])

View File

@ -1,3 +1,9 @@
Version 372, December 2007
Minor bug fixes
----------------------------------------------------------------------
Version 371, August 2007 Version 371, August 2007
Fixed (get-face-list 'mono) for Mac OS X and X11 Fixed (get-face-list 'mono) for Mac OS X and X11

View File

@ -1,15 +1,12 @@
Version 3.99.0.x Version 3.99.0.x
>> See MzScheme_4.txt for information on major changes. >> See MzScheme_4.txt for information on major changes.
Version 371.3 Version 372, December 2007
Added syntax-local-lift-context Added syntax-local-lift-context
Added #lang Added #lang
Version 371.2
Added require-for-label, provide-for-syntax, provide-for-label, Added require-for-label, provide-for-syntax, provide-for-label,
identifier-label-binding, module-label-identifier=? identifier-label-binding, module-label-identifier=?
Version 371, August 2007 Version 371, August 2007
Added hash-table-iterate-{first,next,key,value} Added hash-table-iterate-{first,next,key,value}
Added keyword<? Added keyword<?

View File

@ -4514,6 +4514,7 @@ static int mark_cport_MARK(void *p) {
gcMARK(cp->ut); gcMARK(cp->ut);
gcMARK(cp->symtab); gcMARK(cp->symtab);
gcMARK(cp->insp); gcMARK(cp->insp);
gcMARK(cp->relto);
gcMARK(cp->magic_sym); gcMARK(cp->magic_sym);
gcMARK(cp->magic_val); gcMARK(cp->magic_val);
gcMARK(cp->shared_offsets); gcMARK(cp->shared_offsets);
@ -4530,6 +4531,7 @@ static int mark_cport_FIXUP(void *p) {
gcFIXUP(cp->ut); gcFIXUP(cp->ut);
gcFIXUP(cp->symtab); gcFIXUP(cp->symtab);
gcFIXUP(cp->insp); gcFIXUP(cp->insp);
gcFIXUP(cp->relto);
gcFIXUP(cp->magic_sym); gcFIXUP(cp->magic_sym);
gcFIXUP(cp->magic_val); gcFIXUP(cp->magic_val);
gcFIXUP(cp->shared_offsets); gcFIXUP(cp->shared_offsets);
@ -4611,6 +4613,7 @@ static int mark_delay_load_MARK(void *p) {
gcMARK(ld->symtab); gcMARK(ld->symtab);
gcMARK(ld->shared_offsets); gcMARK(ld->shared_offsets);
gcMARK(ld->insp); gcMARK(ld->insp);
gcMARK(ld->relto);
gcMARK(ld->ut); gcMARK(ld->ut);
gcMARK(ld->current_rp); gcMARK(ld->current_rp);
gcMARK(ld->cached); gcMARK(ld->cached);
@ -4625,6 +4628,7 @@ static int mark_delay_load_FIXUP(void *p) {
gcFIXUP(ld->symtab); gcFIXUP(ld->symtab);
gcFIXUP(ld->shared_offsets); gcFIXUP(ld->shared_offsets);
gcFIXUP(ld->insp); gcFIXUP(ld->insp);
gcFIXUP(ld->relto);
gcFIXUP(ld->ut); gcFIXUP(ld->ut);
gcFIXUP(ld->current_rp); gcFIXUP(ld->current_rp);
gcFIXUP(ld->cached); gcFIXUP(ld->cached);

View File

@ -1840,6 +1840,7 @@ mark_cport {
gcMARK(cp->ut); gcMARK(cp->ut);
gcMARK(cp->symtab); gcMARK(cp->symtab);
gcMARK(cp->insp); gcMARK(cp->insp);
gcMARK(cp->relto);
gcMARK(cp->magic_sym); gcMARK(cp->magic_sym);
gcMARK(cp->magic_val); gcMARK(cp->magic_val);
gcMARK(cp->shared_offsets); gcMARK(cp->shared_offsets);
@ -1877,6 +1878,7 @@ mark_delay_load {
gcMARK(ld->symtab); gcMARK(ld->symtab);
gcMARK(ld->shared_offsets); gcMARK(ld->shared_offsets);
gcMARK(ld->insp); gcMARK(ld->insp);
gcMARK(ld->relto);
gcMARK(ld->ut); gcMARK(ld->ut);
gcMARK(ld->current_rp); gcMARK(ld->current_rp);
gcMARK(ld->cached); gcMARK(ld->cached);

View File

@ -4187,6 +4187,7 @@ typedef struct Scheme_Load_Delay {
Scheme_Object **symtab; Scheme_Object **symtab;
long *shared_offsets; long *shared_offsets;
Scheme_Object *insp; Scheme_Object *insp;
Scheme_Object *relto;
Scheme_Unmarshal_Tables *ut; Scheme_Unmarshal_Tables *ut;
struct CPort *current_rp; struct CPort *current_rp;
int perma_cache; int perma_cache;
@ -4211,6 +4212,7 @@ typedef struct CPort {
Scheme_Object **symtab; Scheme_Object **symtab;
Scheme_Object *insp; /* inspector for module-variable access */ Scheme_Object *insp; /* inspector for module-variable access */
Scheme_Object *magic_sym, *magic_val; Scheme_Object *magic_sym, *magic_val;
Scheme_Object *relto;
long *shared_offsets; long *shared_offsets;
Scheme_Load_Delay *delay_info; Scheme_Load_Delay *delay_info;
} CPort; } CPort;
@ -4735,11 +4737,9 @@ static Scheme_Object *read_compact(CPort *port, int use_stack)
if (scheme_is_relative_path(SCHEME_PATH_VAL(v), SCHEME_PATH_LEN(v), SCHEME_PLATFORM_PATH_KIND)) { if (scheme_is_relative_path(SCHEME_PATH_VAL(v), SCHEME_PATH_LEN(v), SCHEME_PLATFORM_PATH_KIND)) {
/* Resolve relative path using the current load-relative directory: */ /* Resolve relative path using the current load-relative directory: */
Scheme_Object *dir; if (SCHEME_PATHP(port->relto)) {
dir = scheme_get_param(scheme_current_config(), MZCONFIG_LOAD_DIRECTORY);
if (SCHEME_PATHP(dir)) {
Scheme_Object *a[2]; Scheme_Object *a[2];
a[0] = dir; a[0] = port->relto;
a[1] = v; a[1] = v;
v = scheme_build_path(2, a); v = scheme_build_path(2, a);
} }
@ -5109,6 +5109,8 @@ static Scheme_Object *read_compiled(Scheme_Object *port,
Scheme_Hash_Table **local_ht; Scheme_Hash_Table **local_ht;
int all_short; int all_short;
int perma_cache = use_perma_cache; int perma_cache = use_perma_cache;
Scheme_Object *dir;
Scheme_Config *config;
if (USE_LISTSTACK(!p->list_stack)) if (USE_LISTSTACK(!p->list_stack))
scheme_alloc_list_stack(p); scheme_alloc_list_stack(p);
@ -5242,9 +5244,14 @@ static Scheme_Object *read_compiled(Scheme_Object *port,
rp->ht = local_ht; rp->ht = local_ht;
rp->symtab = symtab; rp->symtab = symtab;
insp = scheme_get_param(scheme_current_config(), MZCONFIG_CODE_INSPECTOR); config = scheme_current_config();
insp = scheme_get_param(config, MZCONFIG_CODE_INSPECTOR);
rp->insp = insp; rp->insp = insp;
dir = scheme_get_param(config, MZCONFIG_LOAD_DIRECTORY);
rp->relto = dir;
rp->magic_sym = params->magic_sym; rp->magic_sym = params->magic_sym;
rp->magic_val = params->magic_val; rp->magic_val = params->magic_val;
@ -5276,6 +5283,7 @@ static Scheme_Object *read_compiled(Scheme_Object *port,
delay_info->symtab = rp->symtab; delay_info->symtab = rp->symtab;
delay_info->shared_offsets = rp->shared_offsets; delay_info->shared_offsets = rp->shared_offsets;
delay_info->insp = rp->insp; delay_info->insp = rp->insp;
delay_info->relto = rp->relto;
if (perma_cache) { if (perma_cache) {
unsigned char *cache; unsigned char *cache;
@ -5417,6 +5425,7 @@ Scheme_Object *scheme_load_delayed_code(int _which, Scheme_Load_Delay *_delay_in
rp->ht = ht; rp->ht = ht;
rp->symtab = delay_info->symtab; rp->symtab = delay_info->symtab;
rp->insp = delay_info->insp; rp->insp = delay_info->insp;
rp->relto = delay_info->relto;
rp->shared_offsets = delay_info->shared_offsets; rp->shared_offsets = delay_info->shared_offsets;
rp->delay_info = delay_info; rp->delay_info = delay_info;