diff --git a/collects/scribble/html-render.ss b/collects/scribble/html-render.ss index fe8f45257e..fddce7dab4 100644 --- a/collects/scribble/html-render.ss +++ b/collects/scribble/html-render.ss @@ -130,7 +130,8 @@ `((,(case (length number) [(0) 'h2] [(1) 'h3] - [else 'h4]) + [(2) 'h4] + [else 'h5]) ,@(format-number number '((tt nbsp))) ,@(if (part-tag d) `((a ((name ,(format "~a" `(part ,(part-tag d))))))) diff --git a/collects/scribble/manual.ss b/collects/scribble/manual.ss index d01ed7afa4..521add3b62 100644 --- a/collects/scribble/manual.ss +++ b/collects/scribble/manual.ss @@ -180,7 +180,8 @@ ;; ---------------------------------------- - (provide defproc defproc* defstruct defthing defform defform* defform/subs defform*/subs defform/none + (provide defproc defproc* defstruct defthing defparam + defform defform* defform/subs defform*/subs defform/none specform specform/subs specsubform specsubform/subs specspecsubform specspecsubform/subs specsubform/inline schemegrammar schemegrammar* @@ -240,8 +241,10 @@ (lambda () (list desc ...)))])) (define-syntax defstruct (syntax-rules () + [(_ name fields #:immutable desc ...) + (*defstruct (quote-syntax name) 'name 'fields #t (lambda () (list desc ...)))] [(_ name fields desc ...) - (*defstruct (quote-syntax name) 'name 'fields (lambda () (list desc ...)))])) + (*defstruct (quote-syntax name) 'name 'fields #f (lambda () (list desc ...)))])) (define-syntax (defform*/subs stx) (syntax-case stx () [(_ #:literals (lit ...) [spec spec1 ...] ([non-term-id non-term-form ...] ...) desc ...) @@ -342,6 +345,10 @@ (syntax-rules () [(_ id result desc ...) (*defthing (quote-syntax id) 'id 'result (lambda () (list desc ...)))])) + (define-syntax defparam + (syntax-rules () + [(_ id arg contract desc ...) + (defproc* ([(id) contract] [(id [arg contract]) void?]) desc ...)])) (define-syntax schemegrammar (syntax-rules () [(_ #:literals (lit ...) id clause ...) (*schemegrammar '(lit ...) @@ -587,7 +594,7 @@ (map symbol->string (car wrappers))))))) (cdr wrappers)))) - (define (*defstruct stx-id name fields content-thunk) + (define (*defstruct stx-id name fields immutable? content-thunk) (define spacer (hspace 1)) (make-splice (cons @@ -613,10 +620,13 @@ (map (lambda (f) (list name '- (car f))) fields) - (map (lambda (f) - (list 'set- name '- (car f) '!)) - fields))))) - ,(map car fields)))))))) + (if immutable? + null + (map (lambda (f) + (list 'set- name '- (car f) '!)) + fields)))))) + ,(map car fields) + ,@(if immutable? '(#:immutable) null)))))))) (map (lambda (v) (cond [(pair? v) diff --git a/collects/scribble/scheme.ss b/collects/scribble/scheme.ss index c820bad7fb..c762f20554 100644 --- a/collects/scribble/scheme.ss +++ b/collects/scribble/scheme.ss @@ -111,7 +111,7 @@ (define advance (case-lambda [(c init-line! delta) - (let ([c (+ delta (syntax-column c))] + (let ([c (+ delta (or (syntax-column c) 0))] [l (syntax-line c)]) (let ([new-line? (and l (l . > . line))]) (when new-line? diff --git a/collects/scribble/scribble.css b/collects/scribble/scribble.css index 887ca883e4..2310f499a3 100644 --- a/collects/scribble/scribble.css +++ b/collects/scribble/scribble.css @@ -69,10 +69,6 @@ margin-right: 0em; } - h1,h2,h3,h4,h5,h6 { - margin-top: .5em; - } - .toclink { text-decoration: none; color: blue; diff --git a/collects/scribblings/reference/custodians.scrbl b/collects/scribblings/reference/custodians.scrbl new file mode 100644 index 0000000000..aaba12717e --- /dev/null +++ b/collects/scribblings/reference/custodians.scrbl @@ -0,0 +1,96 @@ +#reader(lib "docreader.ss" "scribble") +@require[(lib "bnf.ss" "scribble")] +@require["mz.ss"] + +@title[#:tag "mz:custodians"]{Custodians} + +See @secref["mz:custodian-model"] for basic information on the PLT +Scheme custodian parameter model. + +@defproc[(make-custodian [cust custodian? (current-custodian)]) custodian?]{ + +Creates a new custodian that is subordinate to @scheme[cust]. When +@scheme[cust] is directed (via @scheme[custodian-shutdown-all]) to +shut down all of its managed values, the new subordinate custodian is +automatically directed to shut down its managed values as well.} + +@defproc[(custodian-shutdown-all [cust custodian?]) void?]{ + +Closes all open ports and closes all active TCP listeners and UDP +sockets that are managed by @scheme[cust]. It also removes +@scheme[cust] (and its subordinates) as managers of all threads; when +a thread has no managers, it is killed (or suspended; see +@scheme[thread/suspend-to-kill]) If the current thread is to be +killed, all other shut-down actions take place before killing the +thread.} + +@defproc[(custodian? [v any/c]) boolean?]{ + +Returns @scheme[#t] if @scheme[v] is a @tech{custodian} value, +@scheme[#f] otherwise. } + +@defproc[(custodian-managed-list [cust custodian?][super custodian?]) list?]{ + +Returns a list of immediately managed objects and subordinate +custodians for @scheme[cust], where @scheme[cust] is itself +subordinate to @scheme[super] (directly or indirectly). If +@scheme[cust] is not strictly subordinate to @scheme[super], the +@exnraise[exn:fail:contract].} + +@defproc[(custodian-memory-accounting-available?) boolean?]{ + +Returns @scheme[#t] if MzScheme is compiled with support for +per-custodian memory accounting, @scheme[#f] otherwise. + +@margin-note{Memory accounting is normally available in PLT Scheme 3m, +which is the main variant of PLT Scheme, and not normally available in +PLT Scheme CGC.}} + +@defproc[(custodian-require-memory [limit-cust custodian?] + [need-amt non-negative-exact-integer?] + [stop-cust custodian?]) void?]{ + +Registers a require check if PLT Scheme is compiled with support for +per-custodian memory accounting, otherwise the +@exnraise[exn:fail:unsupported]. + +If a check is registered, and if PLT Scheme later reaches a state after +garbage collection (see @secref["mz:gc-model"]) where allocating +@scheme[need-amt] bytes charged to @scheme[limit-cust] would fail or +tigger some shutdown, then @scheme[stop-cust] is shut down.} + +@defproc[(custodian-limit-memory [limit-cust custodian?] + [limit-amt non-negative-exact-integer?] + [stop-cust custodian? limit-cust]) void?]{ + +Registers a limit check if PLT Scheme is compiled with support for +per-custodian memory accounting, otherwise the +@exnraise[exn:fail:unsupported]. + +If a check is registered, and if PLT Scheme later reaches a state +after garbage collection (see @secref["mz:gc-model"]) where +@scheme[limit-cust] owns more than @scheme[limit-amt] bytes, then +@scheme[stop-cust] is shut down. + +For reliable shutdown, @scheme[limit-amt] for +@scheme[custodian-limit-memory] must be much lower than the total +amount of memory available (minus the size of memory that is +potentially used and not charged to @scheme[limit-cust]). Moreover, if +indvidual allocations that are initially charged to +@scheme[limit-cust] can be arbitrarily large, then @scheme[stop-cust] +must be the same as @scheme[limit-cust], so that excessively large +immediate allocations can be rejected with an +@scheme[exn:fail:out-of-memory] exception.} + +@defproc[(make-custodian-box [cust custodian?][v any/c]) custodian-box?]{ + +Returns a @deftech{custodian box} that contains @scheme[v] as long as +@scheme[cust] has not been shut down.} + +@defproc[(custodian-box? [v any/c]) boolean?]{Returns @scheme[#t] if + @scheme[v] is a @tech{custodian box} produced by + @scheme[make-custodian-box], @scheme[#f] otherwise.} + +@defproc[(custodian-box-value [cb custodian-box?]) any]{Rturns the + value in the given @tech{custodian box}, or @scheme[#f] if the value + has been removed.} diff --git a/collects/scribblings/reference/exns.scrbl b/collects/scribblings/reference/exns.scrbl new file mode 100644 index 0000000000..44f92db733 --- /dev/null +++ b/collects/scribblings/reference/exns.scrbl @@ -0,0 +1,387 @@ +#reader(lib "docreader.ss" "scribble") +@require[(lib "bnf.ss" "scribble")] +@require["mz.ss"] + +@title[#:tag "mz:exns"]{Exceptions} + +See @secref["mz:exn-model"] for information on the PLT Scheme +exception model. It is based on @cite[#:key "friedman-exns" #:title +"Exception system proposal" #:author "Daniel P. Friedman and +C. T. Haynes and R. Kent Dybvig" #:location +"http://www.cs.indiana.edu/scheme-repository/doc.proposals.exceptions.html" +#:date ""]. + +Whenever a primitive error occurs in PLT Scheme, an exception is +raised. The value that is passed to the current @tech{exception +handler} is always an instance of the @scheme[exn] structure +type. Every @scheme[exn] structure value has a @scheme[message] field +that is a string, the primitive error message. The default exception +handler recognizes exception values with the @scheme[exn?] predicate +and passes the error message to the current error display handler (see +@scheme[error-display-handler]). + +Primitive procedures that accept a procedure argument with a +particular required arity (e.g., @scheme[call-with-input-file], +@scheme[call/cc]) check the argument's arity immediately, raising +@scheme[exn:fail:contract] if the arity is incorrect. + +@;------------------------------------------------------------------------ +@section[#:tag "mz:errorproc"]{Raising Exceptions} + +@defproc[(raise [v any/c]) any]{ + +Raises an exception, where @scheme[v] represents the exception being +raised. The @scheme[v] argument can be anything; it is passed to the +current @deftech{exception handler}. Breaks are disabled from the +time the exception is raised until the exception handler obtains +control, and the handler itself is @scheme[parameterize-break]ed to +disable breaks initially; see @secref["mz:breakhandler"] for more +information on breaks.} + + +@defproc*[([(error [sym symbol?]) any] + [(error [msg string?][v any/c] ...) any] + [(error [src symbol?][format string?][v any/c] ...) any])]{ + +Raises the exception @scheme[exn:fail], which contains an error +string. The different forms produce the error string in different +ways: + +@itemize{ + + @item{@scheme[(error sym)] creates a message string by concatenating + @scheme["error: "] with the string form of @scheme[sym].} + + @item{@scheme[(error msg v ...)] creates a message string by + concatenating @scheme[msg] with string versions of the @scheme[v]s + (as produced by the current error value conversion handler; see + @scheme[error-value->string-handler]). A space is inserted before + each @scheme[v].} + + @item{@scheme[(error src format v ...)] creates a + message string equivalent to the string created by + + @schemeblock[ + (format (string-append "~s: " format) src v ...) + ]} + +} + +In all cases, the constructed message string is passed to +@scheme[make-exn:fail], and the resulting exception is raised.} + +@defproc*[([(raise-user-error [sym symbol?]) any] + [(raise-user-error [msg string?][v any/c] ...) any] + [(raise-user-error [src symbol?][format string?][v any/c] ...) any])]{ + +Like @scheme[error], but constructs an exception with +@scheme[make-exn:fail:user] instead of @scheme[make-exn:fail]. The +default error display handler does not show a ``stack trace'' for +@scheme[exn:fail:user] exceptions (see @secref["mz:contmarks"]), so +@scheme[raise-user-error] should be used for errors that are intended +for end users.} + + +@defproc*[([(raise-type-error [name symbol?][expected string?][v any/c]) any] + [(raise-type-error [name symbol?][expected string?][bad-pos non-negative-exact-integer?][v any/c]) any])]{ + +Creates an @scheme[exn:fail:contract] value and @scheme[raise]s it as +an exception. The @scheme[name] argument is used as the source +procedure's name in the error message. The @scheme[expected] argument +is used as a description of the expected type. + +In the first form, @scheme[v] is the value received by the procedure +that does not have the expected type. + +In the second form, the bad argument is indicated by an index +@scheme[bad-pos] (counting from @math{0}), and all of the original +arguments @scheme[v] are provided (in order). The resulting error +message names the bad argument and also lists the other arguments. If +@scheme[bad-pos] is not less than the number of @scheme[v]s, the +@exnraise[exn:fail:contract].} + +@defproc[(raise-mismatch-error [name symbol?][message string?][v any/c]) any]{ + +Creates an @scheme[exn:fail:contract] value and @scheme[raise]s it as +an exception. The @scheme[name] is used as the source procedure's +name in the error message. The @scheme[message] is the error +message. The @scheme[v] argument is the improper argument received by +the procedure. The printed form of @scheme[v] is appended to +@scheme[message] (using the error value conversion handler; see +@scheme[error-value->string-handler]).} + +@defproc[(raise-arity-error [name (or/c symbol? procedure?)] + [arity-v (or/c exact-nonnegative-integer? + arity-at-least? + (listof + (or/c exact-nonnegative-integer? + arity-at-least?)))] + [arg-v any/c #f] ...) + any] { + +Creates an @scheme[exn:fail:contract:arity] value and @scheme[raise]s +it as an exception. The @scheme[name] is used for the source +procedure's name in the error message. The @scheme[arity-v] value must +be a possible result from @scheme[procedure-arity], and it is used for +the procedure's arity in the error message; if +@scheme[name-symbol-or-procedure] is a procedure, its actual arity is +ignored. The @scheme[arg-v] arguments are the actual supplied +arguments, which are shown in the error message (using the error value +conversion handler; see @scheme[error-value->string-handler]); also, +the number of supplied @scheme[arg-v]s is explicitly mentioned in the +message.} + +@defproc[(raise-syntax-error [name (or/c symbol? false/c)] + [message string?] + [expr any/c #f] + [sub-expr any/c #f]) + any]{ + +Creates an @scheme[exn:fail:syntax] value and @scheme[raise]s it as an +exception. Macros use this procedure to report syntax errors. + +The @scheme[name] argument is usually @scheme[#f] when @scheme[expr] +is provided; it is described in more detail below. The +@scheme[message] is used as the main body of the error message. + +The optional @scheme[expr] argument is the erroneous source syntax +object or S-expression. The optional @scheme[sub-expr] argument is a +syntax object or S-expression within @scheme[expr] that more precisely +locates the error. If @scheme[sub-expr] is provided, it is used (in +syntax form) for the @scheme[exprs] field of the generated exception +record, else the @scheme[expr] is used if provided, otherwise the +@scheme[exprs] field is the empty list. Source location information in +the error-message text is similarly extracted from @scheme[sub-expr] +or @scheme[expr], when at least one is a syntax object. + +The form name used in the generated error message is determined +through a combination of the @scheme[name], @scheme[expr], and +@scheme[sub-expr] arguments: + +@itemize{ + + @item{When @scheme[name] is @scheme[#f], and when @scheme[expr] is + either an identifier or a syntax pair containing an identifier as + its first element, then the form name from the error message is the + identifier's symbol.} + + @item{When @scheme[name] is @scheme[#f] and when @scheme[expr] is not + an identifier or a syntax pair containing and identifier as its + first element, then the form name in the error message is + @scheme["?"].} + + @item{@scheme[symbol]: When @scheme[name] is a symbol, then the symbol + is used as the form name in the generated error message.} + +} + +See also @scheme[error-print-source-location].} + +@;------------------------------------------------------------------------ +@section{Handling Exceptions} + +@defproc[(call-with-exception-handler [f (any/c . -> . any)][thunk (-> any)]) any]{ + +Installs @scheme[f] as the @tech{exception handler} for the current +continuation---i.e., for the dynamic extent of a call to +@scheme[thunk]. The @scheme[thunk] is called in tail position with +respect to the call to @scheme[call-with-exception-handler]. If an +exception is raised during the evaluation of @scheme[thunk] (in an +extension of the current continuation that does not have its own +exception handler), then @scheme[f] is applied to the @scheme[raise]d +value in the continuation of the @scheme[raise] call (but extended +with a continuation barrier; see @secref["mz:continuations"]). + +Any procedure that takes one argument can be an exception handler. If +the exception handler returns a value when invoked by @scheme[raise], +then @scheme[raise] propagates the value to the ``previous'' exception +handler (still in the dynamic extent of the call to +@scheme[raise]). The previous exception handler is the exception +handler associated with the rest of the continuation after the point +where the called exception handler was associated with the +continuation; if no previous handler is available, the +uncaught-exception handler is used (see below). In all cases, a call +to an exception handler is @scheme[parameterize-break]ed to disable +breaks, and it is wrapped with @scheme[call-with-exception-handler] to +install the an exception handler that reports both the original and +newly raised exceptions.} + +@defparam[uncaught-exception-handler f (any/c . -> . any)]{ + +A @tech{parameter} that determines an exception handler used by +@scheme[raise] when the relevant continuation has no exception handler +installed with @scheme[call-with-exception-handler] or +@scheme[with-handlers]. Unlike exception handlers installed with +@scheme[call-with-exception-handler], the handler for uncaught +exceptions must not return a value when called by @scheme[raise]; if +it returns, an exception is raised (to be handled by an exception +handler that reports both the original and newly raised exception). + +The default uncaught-exception handler prints an error message using +the current error display handler (see @scheme[error-display-handler]) +and then escapes by calling the current error escape handler (see +@scheme[error-escape-handler]). The call to each handler is +@scheme[parameterize]d to set @scheme[error-display-handler] to the +default error display handler, and it is @scheme[parameterize-break]ed +to disable breaks. The call to the error escape handler is further +parameterized to set @scheme[error-escape-handler] to the default +error escape handler. + +When the current error display handler is the default handler, then the +error-display call is parameterized to install an emergency error +display handler that attempts to print directly to a console and never +fails.} + +@defform[(with-handlers ((pred-expr handler-expr)) + body ...+)]{ + +Evaluates each @scheme[pred-expr] and and @scheme[handler-expr] in the +order that they are specified, and then evaluates the @scheme[body]s +with a new exception handler during the its dynamic extent. + +The new exception handler processes an exception only if one of the +@scheme[pred-expr] procedures returns a true value when applied to the +exception, otherwise the exception handler is invoked from the +continuation of the @scheme[with-handlers] expression (by raising the +exception again). If an exception is handled by one of the +@scheme[handler-expr] procedures, the result of the entire +@scheme[with-handlers] expression is the return value of the handler. + +When an exception is raised during the evaluation of @scheme[body]s, +each predicate procedure @scheme[pred-expr] is applied to the +exception value; if a predicate returns a true value, the +corresponding @scheme[handler-expr] procedure is invoked with the +exception as an argument. The predicates are tried in the order that +they are specified. + +Before any predicate or handler procedure is invoked, the continuation +of the entire @scheme[with-handlers] expression is restored, but also +@scheme[parameterize-break]ed to disable breaks. Thus, breaks are +disabled by default during the predicate and handler procedures (see +@secref["mz:breakhandler"]), and the exception handler is the one from +the continuation of the @scheme[with-handlers] expression. + +The @scheme[exn:fail?] procedure is useful as a handler predicate to +catch all error exceptions. Avoid using @scheme[(lambda (x) #t)] as a +predicate, because the @scheme[exn:break] exception typically should +not be caught (unless it will be re-raised to cooperatively +break). Beware, also, of catching and discarding exceptions, because +discarding an error message can make debugging unnecessarily +difficult.} + +@defform[(with-handlers* ((pred-expr handler-expr)) + body ...+)]{ + +Like @scheme[with-handlers], but if a @scheme[handler-expr] procedure +is called, breaks are not explicitly disabled, and the call is in tail +position with respect to the @scheme[with-handlers*] form.} + +@;------------------------------------------------------------------------ +@section{Built-in Exception Types} + +@defstruct[exn ([message string?] + [continuation-marks continuation-mark-set?]) + #:immutable]{ + +The base @tech{structure type} for exceptions. The @scheme[message] +field contains an error message, and the @scheme[continuation-marks] +field contains the value produced by @scheme[(current-continuation-marks)] +immediately before the exception was raised.} + +@defstruct[(exn:fail exn) ()]{ + +Raised for exceptions that represent errors, as opposed to +@scheme[exn:break].} + + +@defstruct[(exn:fail:contract exn:fail) ()]{ + +Raised for errors from the inappropriate run-time use of a function or +syntactic form.} + +@defstruct[(exn:fail:contract:arity exn:fail:contract) ()]{ + +Raised when a procedure is applied to the wrong number of arguments.} + +@defstruct[(exn:fail:contract:divide-by-zero exn:fail:contract) ()]{ + +Raised for division by exact zero.} + +@defstruct[(exn:fail:contract:continuation exn:fail:contract) ()]{ + +Raised when a continuation is applied where the jump would cross a +continuation barrier.} + +@defstruct[(exn:fail:contract:variable exn:fail:contract) ([id symbol?]) + #:immutable]{ + +Raised for a reference to a not-yet-defined @tech{top-level variable} +or @tech{module-level variable}.} + +@defstruct[(exn:fail:syntax exn:fail) ([exprs (listof syntax?)]) + #:immutable]{ + +Raised for a syntax error that is not a @scheme[read] error. The +@scheme[exprs] indicate the relevant source expressions, +least-specific to most-specific.} + + +@defstruct[(exn:fail:read exn:fail) ([srclocs (listof srcloc?)]) + #:immutable]{ + +Raised for a @scheme[read] error. The @scheme[srclocs] indicate the +relevant source expressions.} + +@defstruct[(exn:fail:read:eof exn:fail:read) ()]{ + +Raised for a @scheme[read] error, specifically when the error is due +to an unexpected end-of-file.} + +@defstruct[(exn:fail:read:non-char exn:fail:read) ()]{ + +Raised for a @scheme[read] error, specifically when the error is due +to an unexpected non-character (i.e., ``special'') element in the +input stream.} + +@defstruct[(exn:fail:filesystem exn:fail) ()]{ + +Raised for an error related to the filesystem (such as a file not +found).} + +@defstruct[(exn:fail:filesystem:exists exn:fail:filesystem) ()]{ + +Raised for an error when attempting to create a file that exists +already.} + +@defstruct[(exn:fail:filesystem:version exn:fail:filesystem) ()]{ + +Raised for a version-mismatch error when loading an extension.} + + +@defstruct[(exn:fail:network exn:fail) ()]{ + +Raised for TCP and UDP errors.} + + +@defstruct[(exn:fail:out-of-memory exn:fail) ()]{ + +Raised for an error due to insufficient memory, in cases where sufficient +memory is at least available for raising the exception.} + +@defstruct[(exn:fail:unsupported exn:fail) ()]{ + +Raised for an error due to an unsupported feature on the current +platform or configuration.} + +@defstruct[(exn:fail:user exn:fail) ()]{ + +Raised for errors that are intended to be seen by end-users. In +particular, the default error printer does not show the program +context when printing the error message.} + +@defstruct[(exn:break exn) ([continuation continuation?]) + #:immutable]{ + +Raised asynchronously (when enabled) in response to a break request. +The @scheme[continuation] field can be used by a handler to resume the +interrupted computation.} diff --git a/collects/scribblings/reference/model.scrbl b/collects/scribblings/reference/model.scrbl index 41f9365b66..7c6f2de5a9 100644 --- a/collects/scribblings/reference/model.scrbl +++ b/collects/scribblings/reference/model.scrbl @@ -332,7 +332,7 @@ The behavior of a datatype with respect to @scheme[eq?] is generally specified with the datatype and its associated procedures. @;------------------------------------------------------------------------ -@section{Garbage Collection} +@section[#:tag "mz:gc-model"]{Garbage Collection} In the program state @@ -523,15 +523,18 @@ the evaluation of @scheme[(require m)] creates the variable @scheme[x] and installs @scheme[10] as its value. This @scheme[x] is unrelated to any top-level definition of @scheme[x]. -Another difference is that a module can be @tech{instantiate}d in -multiple @deftech{phases}. A phase is an integer that, again, is -effectively a prefix on the names of module-level definitions. A -top-level @scheme[require] @tech{instantiates} a module at -@tech{phase} 0, if the module is not already @tech{instantiate}d at -phase 0. A top-level @scheme[require-for-syntax] @tech{instantiates} -a module at @tech{phase} 1 (if it is not already @tech{instantiate}d -at that level); a @scheme[require-for-syntax] also has a different -binding effect on further program parsing, as described in +@;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - +@subsection[#:tag "mz:module-phase"]{Module Phases} + +A module can be @tech{instantiate}d in multiple @deftech{phases}. A +phase is an integer that, again, is effectively a prefix on the names +of module-level definitions. A top-level @scheme[require] +@tech{instantiates} a module at @tech{phase} 0, if the module is not +already @tech{instantiate}d at phase 0. A top-level +@scheme[require-for-syntax] @tech{instantiates} a module at +@tech{phase} 1 (if it is not already @tech{instantiate}d at that +level); a @scheme[require-for-syntax] also has a different binding +effect on further program parsing, as described in @secref["mz:intro-binding"]. Within a module, some definitions are shifted by a phase already; the @@ -562,6 +565,21 @@ multiple @tech{instantiations} may exist at phase 1 and higher. These @secref["mz:mod-parse"]), and are, again, conceptually distinguished by prefixes. +@;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - +@subsection[#:tag "mz:module-redeclare"]{Module Re-declarations} + +When a module is declared using a name for which a module is already +declared, the new declaration's definitions replace and extend the old +declarations. If a variable in the old declaration has no counterpart +in the new declaration, the old variable continues to exist, but its +binding is not included in the @tech{lexical information} for the +module body. If a new variable definition has a counterpart in the old +declaration, it effectively assigns to the old variable. + +If a module is @tech{instantiate}d in any @tech{phase}s before it is +re-declared, each re-declaration of the module is immediately +@tech{instantiate}d in the same @tech{phase}s. + @;------------------------------------------------------------------------ @section{Continuation Frames and Marks} @@ -598,7 +616,7 @@ prompt with another one. When a delimited continuation is captured, the marks associated with the relevant frames are also captured. @;------------------------------------------------------------------------ -@section{Threads} +@section[#:tag "mz:thread-model"]{Threads} Scheme supports multiple, pre-emptive threads of evaluation. In terms of the evaluation model, this means that each step in evaluation @@ -621,7 +639,7 @@ new thread sees the same initial value (specified when the thread cell is created) as all other threads. @;------------------------------------------------------------------------ -@section{Parameters} +@section[#:tag "mz:parameter-model"]{Parameters} @deftech{Parameters} are essentially a derived concept in Scheme; they are defined in terms of continuation marks and thread cells. However, @@ -648,7 +666,7 @@ Various operations, such as @scheme[parameterize] or current continuation's frame. @;------------------------------------------------------------------------ -@section{Exceptions} +@section[#:tag "mz:exn-model"]{Exceptions} @deftech{Exceptions} are essentially a derived concept in Scheme; they are defined in terms of continuations, prompts, and continuation @@ -669,4 +687,67 @@ particular tag for which a prompt is always present, because the prompt is installed in the outermost frame of the continuation for any new thread. +@;------------------------------------------------------------------------ +@section[#:tag "mz:custodian-model"]{Custodians} +A @deftech{custodian} manages a collection of threads, file-stream +ports, TCP ports, TCP listeners, UDP sockets, and byte converters. +Whenever a thread, file-stream port, TCP port, TCP listener, or UDP +socket is created, it is placed under the management of the +@deftech{current custodian} as determined by the +@scheme[current-custodian] @tech{parameter}. + +@margin-note{In MrEd, custodians also manage eventspaces.} + +Except for the root custodian, every @tech{custodian} itself it +managed by a @tech{custodian}, so that custodians form a hierarchy. +Every object managed by a subordinate custodian is also managed by the +custodian's owner. + +When a @tech{custodian} is shut down via +@scheme[custodian-shutdown-all], it forcibly and immediately closes +the ports, TCP connections, etc. that it manages, as well as +terminating (or suspending) its threads. A custodian that has been +shut down cannot manage new objects. If the current custodian is shut +down before a procedure is called to create a managed resource (e.g., +@scheme[open-input-port], @scheme[thread]), the +@exnraise[exn:fail:contract]. + +A thread can have multiple managing custodians, and a suspended thread +created with @scheme[thread/suspend-to-kill] can have zero +custodians. Extra custodians become associated with a thread through +@scheme[thread-resume] (see @secref["mz:threadkill"]). When a thread +has multiple custodians, it is not necessarily killed by a +@scheme[custodian-shutdown-all], but shut-down custodians are removed +from the thread's managing set, and the thread is killed when its +managing set becomes empty. + +The values managed by a custodian are only weakly held by the +custodian. As a result, a @tech{will} can be executed for a value that +is managed by a custodian. In addition, a custodian only weakly +references its subordinate custodians; if a subordinate custodian is +unreferenced but has its own subordinates, then the custodian may be +collected, at which point its subordinates become immediately +subordinate to the collected custodian's superordinate custodian. + +In addition to the other entities managed by a custodian, a +@defterm{custodian box} created with @scheme[make-custodian-box] +strongly holds onto a value placed in the box until the box's +custodian is shut down. The custodian only weakly retains the box +itself, however (so the box and its content can be collected if there +are no other references to them). + +When MzScheme is compiled with support for per-custodian memory +accounting (see @scheme[custodian-memory-accounting-available?]), the +@scheme[current-memory-use] procedure can report a custodian-specific +result. This result determines how much memory is occupied by objects +that are reachable from the custodian's managed values, especially its +threads, and including its sub-custodians' managed values. If an +object is reachable from two custodians where neither is an ancestor +of the other, an object is arbitrarily charged to one of the other, +and the choice can change after each collection; objects reachable +from both a custodian and its descendant, however, are reliably +charged to the descendant. Reachability for per-custodian accounting +does not include weak references, references to threads managed by +non-descendant custodians, references to non-descendant custodians, or +references to custodian boxes for non-descendant custodians. diff --git a/collects/scribblings/reference/reference.scrbl b/collects/scribblings/reference/reference.scrbl index 286529b116..f3e690cbdd 100644 --- a/collects/scribblings/reference/reference.scrbl +++ b/collects/scribblings/reference/reference.scrbl @@ -29,6 +29,9 @@ language. @;------------------------------------------------------------------------ @include-section["regexps.scrbl"] +@include-section["exns.scrbl"] +@include-section["threads.scrbl"] +@include-section["custodians.scrbl"] @;------------------------------------------------------------------------ diff --git a/collects/scribblings/reference/syntax-model.scrbl b/collects/scribblings/reference/syntax-model.scrbl index 0dcb43fe16..76d78ce42a 100644 --- a/collects/scribblings/reference/syntax-model.scrbl +++ b/collects/scribblings/reference/syntax-model.scrbl @@ -498,14 +498,29 @@ and evaluated in the same way as for @scheme[syntax]. However, the introduced binding is a normal binding at phase level 1 (not a @tech{transformer binding} at phase level 0). +@;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - +@subsection[#:tag "mz:partial-expansion"]{Partial Expansion} + +In certain contexts, such as an @tech{internal-definition context} or +@tech{module context}, forms are partially expanded to determine +whether they represent definitions, expressions, or other declaration +forms. Partial expansion works by cutting off the normal recursion +expansion when the relevant binding is for a primitive syntactic form. + +As a special case, when expansion would otherwise add an +@schemeidfont{#%app}, @schemeidfont{#%datum}, or @schemeidfont{#%top} +identifier to an expression, and when the binding turns out to be the +primitive @scheme[#%app], @scheme[#%datum], or @scheme[#%top] form, +then expansion stops without adding the identifier. + @;- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - @subsection[#:tag "mz:intdef-body"]{Internal Definitions} -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: +An internal-definition context corresponds to a partial expansion step +(see @secref["mz:partial-expansion"]). 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{ diff --git a/collects/scribblings/reference/syntax.scrbl b/collects/scribblings/reference/syntax.scrbl index ff612e9f9d..d59ff0b9f7 100644 --- a/collects/scribblings/reference/syntax.scrbl +++ b/collects/scribblings/reference/syntax.scrbl @@ -499,10 +499,11 @@ position with respect to the @scheme[if] form. (code:line keyword arg-id) (code:line keyword [arg-id default-expr])])]{ -The first form binds @scheme[id] to the result of @scheme[expr], and -the second form binds @scheme[id] to a procedure. In the second case, -the generation procedure is @scheme[(#,cvt (head args) body ...+)], -using the @|cvt| meta-function defined as follows: +The first form @tech{bind}s @scheme[id] to the result of +@scheme[expr], and the second form @tech{bind}s @scheme[id] to a +procedure. In the second case, the generation procedure is +@scheme[(#,cvt (head args) body ...+)], using the @|cvt| meta-function +defined as follows: @schemeblock[ (#,cvt (id . _gen-formals) . _datum) = (lambda _gen-formals . _datum) @@ -535,7 +536,7 @@ x @defform[(define-values (id ...) expr)]{ -Evaluates the @scheme[expr], and binds the results to the +Evaluates the @scheme[expr], and @tech{bind}s the results to the @scheme[id]s, in order, if the number of results matches the number of @scheme[id]s; if @scheme[expr] produces a different number of results, the @exnraise[exn:fail:contract]. @@ -609,7 +610,8 @@ in tail position only if no @scheme[body]s are present. Evaluates @scheme[expr] and installs the result into the location for @scheme[id], which must be bound as a local variable or defined as a @tech{top-level variable} or @tech{module-level variable}. If -@scheme[id] refers to a @tech{top-level variable} that has not been +@scheme[id] refers to an imported binding, a syntax error is reported. +If @scheme[id] refers to a @tech{top-level variable} that has not been defined, the @exnraise[exn:fail:contract]. @defexamples[ @@ -668,11 +670,89 @@ information} and source-location information attached to Declares a module named by @scheme[id]. The @scheme[require-spec] must be as for @scheme[require] (see @secref["mz:require"]), and it -supplies the initial bindings for the body @scheme[form]s. Each -@scheme[form] is expanded in a @tech{module context}. +supplies the initial bindings for the body @scheme[form]s. That is, it +is treated like a @scheme[(require require-spec)] prefix on +@scheme[form], where @scheme[require] is the preimitive +@scheme[require] form. + +If a single @scheme[form] is provided, then it is partially expanded +in a @tech{module-begin context}. If the expansion leads to +@scheme[#%plain-module-begin], then the body of the +@scheme[#%plain-module-begin] is the body of the module. If partial +expansion leads to any other primitive form, then the form is wrapped +with @schemeidfont{#%module-begin} using the lexical context of the +module body; this identifier must be bound by the initial +@scheme[require-spec] import, and its expansion must produce a +@scheme[#%plain-module-begin] to supply the module body. Finally, if +multiple @scheme[form]s are provided, they are wrapped with +@schemeidfont{#%module-begin}, as in the case where a single +@scheme[form] does not expand to @scheme[#%plain-module-begin]. + +Each @scheme[form] is partially expanded (see +@secref["mz:partial-expansion"]) in a @tech{module context}. Further +action depends on the shape of the form: + +@itemize{ + + @item{If it is a @scheme[begin] form, so the sub-forms are flattened + out into the module's body and immediately processed in place of the + @scheme[begin].} + + @item{If it is a @scheme[define-syntaxes] or + @scheme[define-values-for-syntax] form, then the right-hand side is + evaluated (in @tech{phase} 1), and the binding is immediately + installed for further partial expansion within the module.} + + @item{If the form is a @scheme[require], @scheme[require-for-syntax], + or @scheme[require-for-template] form, bindings are introduced + immediately, and the imported modules are @tech{instantiate}d or + @tech{visit}ed as appropriate.} + + @item{If the form is a @scheme[provide] or + @scheme[provide-for-syntax] form, then it is recorded for + processing after the rest of the body.} + + @item{If the form is a @scheme[define-values] form, then the binding + is installed immediately, but the right-hand expression is not + expanded further.} + + @item{Similarly, if the form is an expression, it is + not expanded further.} } +After all @scheme[form]s have been partially expanded this way, then +the remaining expression forms (including those on the right-hand side +of a definition) are expanded in an expression context. + +The scope of all imported identifiers covers the entire module body, +as does the scope of any identifier defined within the module body. +The ordering of syntax definitions does not affect the scope of the +syntax names; a transformer for @scheme[A] can produce expressions +containing @scheme[B], while the transformer for @scheme[B] produces +expressions containing @scheme[A], regardless of the order of +declarations for @scheme[A] and @scheme[B]. However, a syntactic form +that produces syntax definitions must be defined before it is used. + +No identifier can be imported or defined more than once at any +@tech{phase level}. Every exported identifier must be imported or +defined. No expression can refer to a @tech{top-level variable}. + +The evaluation of a @scheme[module] form does not evaluate the +expressions in the body of the module. Evaluation merely declares a +module, whose full name depends both on @scheme[id] and +@scheme[(current-module-name-prefix)]. + +The module body is executed only when the module is explicitly +@techlink{instantiate}d via @scheme[require], +@scheme[require-for-syntax], @scheme[require-for-template], or +@scheme[dynamic-require]. On invocation, expressions and definitions +are evaluated in order as they appear within the module; accessing a +@tech{module-level variable} before it is defined signals a run-time +error, just like accessing an undefined global variable. + +See also @secref["mz:module-eval-model"] and @secref["mz:mod-parse"].} + @;------------------------------------------------------------------------ @section[#:tag "mz:require"]{Importing: @scheme[require], @scheme[require-for-syntax], @scheme[require-for-template]} diff --git a/collects/scribblings/reference/threads.scrbl b/collects/scribblings/reference/threads.scrbl new file mode 100644 index 0000000000..24d0103bdc --- /dev/null +++ b/collects/scribblings/reference/threads.scrbl @@ -0,0 +1,132 @@ +#reader(lib "docreader.ss" "scribble") +@require[(lib "bnf.ss" "scribble")] +@require["mz.ss"] + +@title[#:tag "mz:threads"]{Threads} + +See @secref["mz:thread-model"] and @secref["mz:parameter-model"] for +basic information on the PLT Scheme thread and parameter model. + +When a thread is created, it is placed into the management of the +@tech{current custodian} and added to the current thread group (see +@secref["mz:threadgroups"]). A thread can have any number of custodian +managers added through @scheme[thread-resume]. + +A thread that has not terminated can be garbage collected (see +@secref["mz:gc-model"]) if it is unreachable and suspended, or if it +is unreachable and blocked on a set of unreachable events through +@scheme[semaphore-wait] or @scheme[semaphore-wait/enable-break], +@scheme[channel-put] or @scheme[channel-get], @scheme[sync] or +@scheme[sync/enable-break], or @scheme[thread-wait]. + +@margin-note{In MrEd, a handler thread for an eventspace is blocked on +an internal semaphore when its event queue is empty. Thus, the handler +thread is collectible when the eventspace is unreachable and contains +no visible windows or running timers.} + +All constant-time procedures and operations provided by MzScheme are +thread-safe because they are @defterm{atomic}. For example, +@scheme[set!] assigns to a variable as an atomic action with respect +to all threads, so that no thread can see a ``half-assigned'' +variable. Similarly, @scheme[vector-set!] assigns to a vector +atomically. The @scheme[hash-table-put!] procedure is not atomic, but +the table is protected by a lock; see @secref["mz:hashtable"] for more +information. Port operations are generally not atomic, but they are +thread-safe in the sense that a byte consumed by one thread from an +input port will not be returned also to another thread, and procedures +like @scheme[port-commit-peeked] and @scheme[write-bytes-avail] offer +specific concurrency guarantees. + +@;------------------------------------------------------------------------ +@section{Creating Threads} + +@defproc[(thread [thunk (-> any)]) thread?]{ + +Calls @scheme[thunk] with no arguments in a new thread of control. The +@scheme[thread] procedure returns immediately with a @deftech{thread +descriptor} value. When the invocation of @scheme[thunk] returns, the +thread created to invoke @scheme[thunk] terminates. + +} + +@defproc[(thread? [v any/c]) thread?]{Returns @scheme[#t] if +@scheme[v] is a @tech{thread descriptor}, @scheme[#f] otherwise.} + +@defproc[(current-thread) thread?]{Returns the @tech{thread + descriptor} for the currently executing thread.} + +@defproc[(thread/suspend-to-kill [thunk (-> any)]) thread]{ + +Like @scheme[thread], except that ``killing'' the thread through +@scheme[kill-thread] or @scheme[custodian-shutdown-all] merely +suspends the thread instead of terminating it. } + +@;------------------------------------------------------------------------ +@section[#:tag "mz:threadkill"]{Suspending, Resuming, and Killing Threads} + +@defproc[(thread-suspend [thd thread?]) void?]{ + +Immediately suspends the execution of @scheme[thd] if it is +running. If the thread has terminated or is already suspended, +@scheme[thread-suspend] has no effect. The thread remains suspended +(i.e., it does not execute) until it is resumed with +@scheme[thread-resume]. If the @tech{current custodian} does not +manage @scheme[thd] (and none of its subordinates manages +@scheme[thd]), the @exnraise[exn:fail:contract], and the thread is not +suspended.} + +@defproc[(thread-resume [thd thread?][benefactor (or/c thread? custodian? false/c) #f]) void?]{ + +Resumes the execution of @scheme[thd] if it is suspended and has at +least one custodian (possibly added through @scheme[benefactor], as +described below). If the thread has terminated, or if the thread is +already running and @scheme[benefactor] is not supplied, or if the +thread has no custodian and @scheme[benefactor] is not supplied, then +@scheme[thread-resume] has no effect. Otherwise, if +@scheme[benefactor] is supplied, it triggers up to three +additional actions: + +@itemize{ + + @item{If @scheme[benefactor] is a thread, whenever it is resumed + from a suspended state in the future, then @scheme[thd] is also + resumed. (Resuming @scheme[thd] may trigger the resumption of other + threads that were previously attached to @scheme[thd] through + @scheme[thread-resume].)} + + @item{New custodians may be added to @scheme[thd]'s set of + managers. If @scheme[benefactor] is a thread, then all of the + thread's custodians are added to @scheme[thd]. Otherwise, + @scheme[benefactor] is a custodian, and it is added to @scheme[thd] + (unless the custodian is already shut down). If @scheme[thd] + becomes managed by both a custodian and one or more of its + subordinates, the redundant subordinates are removed from + @scheme[thd]. If @scheme[thd] is suspended and a custodian is + added, then @scheme[thd] is resumed only after the addition.} + + @item{If @scheme[benefactor] is a thread, whenever it receives a + new managing custodian in the future, then @scheme[thd] also + receives the custodian. (Adding custodians to @scheme[thd] may + trigger adding the custodians to other threads that were previously + attached to @scheme[thd] through @scheme[thread-resume].)} + +}} + + +@defproc[(kill-thread [thd thread?]) void?]{ + +Terminates the specified thread immediately, or suspends the thread if +@scheme[thd] was created with +@scheme[thread/suspend-to-kill]. Terminating the main thread exits the +application. If @scheme[thd] has already terminated, +@scheme[kill-thread] does nothing. If the @tech{current custodian} +does not manage @scheme[thd] (and none of its subordinates manages +@scheme[thd]), the @exnraise[exn:fail:contract], and the thread is not +killed or suspended. + +Unless otherwise noted, procedures provided by MzScheme (and MrEd) are +kill-safe and suspend-safe; that is, killing or suspending a thread +never interferes with the application of procedures in other +threads. For example, if a thread is killed while extracting a +character from an input port, the character is either completely +consumed or not consumed, and other threads can safely use the port.}