diff --git a/collects/data/scribblings/queue.scrbl b/collects/data/scribblings/queue.scrbl index ed2650e7df..ed11262a66 100644 --- a/collects/data/scribblings/queue.scrbl +++ b/collects/data/scribblings/queue.scrbl @@ -1,6 +1,7 @@ #lang scribble/manual -@(require scribble/eval "utils.rkt" (for-label racket data/queue)) -@(define qeval (eval/require 'data/queue)) +@(require scribble/eval (for-label racket data/queue)) +@(define qeval (make-base-eval)) +@(qeval '(require data/queue)) @title{Imperative Queues} diff --git a/collects/data/scribblings/utils.rkt b/collects/data/scribblings/utils.rkt deleted file mode 100644 index 6cbde45fe3..0000000000 --- a/collects/data/scribblings/utils.rkt +++ /dev/null @@ -1,9 +0,0 @@ -#lang at-exp racket/base -(require scribble/base scribble/manual scribble/core scribble/eval) -(provide eval/require) - -(define (eval/require . paths) - (let* ([e (make-base-eval)]) - (for ([path (in-list paths)]) - (e `(require ,path))) - e)) diff --git a/collects/unstable/scribblings/bytes.scrbl b/collects/unstable/scribblings/bytes.scrbl index 7d7141133c..40616456d6 100644 --- a/collects/unstable/scribblings/bytes.scrbl +++ b/collects/unstable/scribblings/bytes.scrbl @@ -1,11 +1,7 @@ #lang scribble/doc -@(require scribble/base - scribble/manual - "utils.rkt" - (for-label unstable/bytes - racket/serialize - racket/contract - racket/base)) +@(require scribble/base scribble/manual "utils.rkt" + (for-label racket/base unstable/bytes racket/serialize + racket/contract)) @title[#:tag "bytes"]{Bytes} @@ -16,7 +12,7 @@ @defproc[(bytes-ci=? [b1 bytes?] [b2 bytes?]) boolean?]{ Compares two bytes case insensitively. } - + @defproc[(read/bytes [b bytes?]) serializable?]{ @racket[read]s a value from @racket[b] and returns it. diff --git a/collects/unstable/scribblings/class-iop.scrbl b/collects/unstable/scribblings/class-iop.scrbl index 372d7888aa..24ea507226 100644 --- a/collects/unstable/scribblings/class-iop.scrbl +++ b/collects/unstable/scribblings/class-iop.scrbl @@ -6,11 +6,11 @@ racket/contract racket/base)) -@title[#:tag "class-iop"]{Interface-Oriented Programming for Classes} - @(define the-eval (make-base-eval)) @(the-eval '(require racket/class unstable/class-iop (for-syntax racket/base))) +@title[#:tag "class-iop"]{Interface-Oriented Programming for Classes} + @defmodule[unstable/class-iop] @unstable[@author+email["Ryan Culpepper" "ryanc@racket-lang.org"]] diff --git a/collects/unstable/scribblings/contract.scrbl b/collects/unstable/scribblings/contract.scrbl index ae95e887fc..f0ea33378d 100644 --- a/collects/unstable/scribblings/contract.scrbl +++ b/collects/unstable/scribblings/contract.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/contract)) +@(define the-eval (make-base-eval)) +@(the-eval '(require racket/contract racket/dict unstable/contract)) + @title[#:tag "contract"]{Contracts} @defmodule[unstable/contract] @@ -195,7 +198,7 @@ result is not guaranteed to be the same kind of sequence as the original value; for instance, a wrapped list is not guaranteed to satisfy @scheme[list?]. @defexamples[ -#:eval (eval/require 'racket/contract 'unstable/contract) +#:eval the-eval (define/contract predicates (sequence/c (-> any/c boolean?)) (list integer? string->symbol)) @@ -214,7 +217,7 @@ dictionary as the original value; for instance, a wrapped hash table is not guaranteed to satisfy @scheme[hash?]. @defexamples[ -#:eval (eval/require 'racket/contract 'racket/dict 'unstable/contract) +#:eval the-eval (define/contract table (dict/c symbol? string?) (make-immutable-hash (list (cons 'A "A") (cons 'B 2) (cons 3 "C")))) @@ -231,3 +234,5 @@ immutable dictionaries (which may be passed through a constructor that involves efficient than the original dictionaries. } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/debug.scrbl b/collects/unstable/scribblings/debug.scrbl index 889952da6c..8420bcafc2 100644 --- a/collects/unstable/scribblings/debug.scrbl +++ b/collects/unstable/scribblings/debug.scrbl @@ -2,6 +2,9 @@ @(require scribble/eval "utils.rkt" (for-label racket unstable/debug unstable/syntax)) +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/debug)) + @title{Debugging} @defmodule[unstable/debug] @@ -22,7 +25,7 @@ current error port. The name and source location of the expression may be overridden by keyword options; their defaults are the syntactic form of the expression and its syntactic source location, respectively. -@examples[#:eval (eval/require 'unstable/debug) +@examples[#:eval the-eval (debug 0) (debug #:name "one, two, three" (values 1 2 3)) (debug #:source (make-srcloc 'here 1 2 3 4) @@ -37,7 +40,7 @@ Constructs a message in the same manner as @scheme[format] and writes it to @scheme[(current-error-port)], with indentation reflecting the number of nested @scheme[debug] forms. -@examples[#:eval (eval/require 'unstable/debug) +@examples[#:eval the-eval (dprintf "level: ~a" 0) (debug (dprintf "level: ~a" 1)) (debug (debug (dprintf "level: ~a" 2))) @@ -53,7 +56,7 @@ Constructs a message in the same manner as @scheme[format] and writes it to Logs debugging information for @scheme[(#%app function-expr argument ...)], including the evaluation and results of the function and each argument. -@examples[#:eval (eval/require 'unstable/debug) +@examples[#:eval the-eval (debugf + 1 2 3) ] @@ -91,3 +94,5 @@ expressions in @scheme[begin], @scheme[define], @scheme[define/private], @scheme[with-syntax*], and @scheme[parameterize]. } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/define.scrbl b/collects/unstable/scribblings/define.scrbl index ad91413306..23225004c0 100644 --- a/collects/unstable/scribblings/define.scrbl +++ b/collects/unstable/scribblings/define.scrbl @@ -1,11 +1,10 @@ #lang scribble/manual -@(require - scribble/eval - "utils.rkt" - (for-label - racket - unstable/define - (only-in mzlib/etc define-syntax-set))) +@(require scribble/eval "utils.rkt" + (for-label racket unstable/define + (only-in mzlib/etc define-syntax-set))) + +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/define (for-syntax racket/base))) @title{Definitions} @@ -23,7 +22,7 @@ When used at the top level of a module, evaluates @scheme[expr] at the end of the module. This can be useful for calling functions before their definitions. @defexamples[ -#:eval (eval/require 'unstable/define) +#:eval the-eval (module Failure scheme (f 5) (define (f x) x)) @@ -58,7 +57,7 @@ Racket with different bindings, to provide an implementation of a binding for versions that do not have it but use the built-in one in versions that do. @defexamples[ -#:eval (eval/require 'unstable/define) +#:eval the-eval (define-if-unbound x 1) x (define y 2) @@ -81,7 +80,7 @@ for each @scheme[new] identifier, redirecting it to the corresponding @scheme[old] identifier. @defexamples[ -#:eval (eval/require 'unstable/define) +#:eval the-eval (define-renaming use #%app) (define-renamings [def define] [lam lambda]) (def plus (lam (x y) (use + x y))) @@ -109,7 +108,7 @@ Defines the form @scheme[name] as a shorthand for setting the parameter to @scheme[(parameterize ([parameter value]) body ...)]. @defexamples[ -#:eval (eval/require 'unstable/define) +#:eval the-eval (define-with-parameter with-input current-input-port) (with-input (open-input-string "Tom Dick Harry") (read)) ] @@ -124,7 +123,7 @@ definition form with function shorthand like @scheme[define] and which works like @scheme[define-values] or @scheme[define-syntaxes]. @defexamples[ -#:eval (eval/require 'unstable/define) +#:eval the-eval (define-single-definition define-like define-values) (define-like x 0) x @@ -148,7 +147,7 @@ Especially useful for mutually recursive expander functions and phase 1 macro definitions. Subsumes the behavior of @racket[define-syntax-set]. @defexamples[ -#:eval (eval/require 'unstable/define '(for-syntax racket/base)) +#:eval the-eval (define-syntax-block ([implies expand-implies] nand) @@ -183,3 +182,5 @@ Executes @scheme[e] during phase 1 (the syntax transformation phase) relative to its context, during pass 2 (after head expansion). } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/dict.scrbl b/collects/unstable/scribblings/dict.scrbl index f6fff056c0..383d08f1af 100644 --- a/collects/unstable/scribblings/dict.scrbl +++ b/collects/unstable/scribblings/dict.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/dict)) +@(define the-eval (make-base-eval)) +@(the-eval '(require racket/dict unstable/dict)) + @title{Dictionaries} @defmodule[unstable/dict] @@ -14,7 +17,7 @@ This module provides tools for manipulating dictionary values. Reports whether @scheme[d] is empty (has no keys). @defexamples[ -#:eval (eval/require 'racket/dict 'unstable/dict) +#:eval the-eval (dict-empty? '()) (dict-empty? '([1 . one] [2 . two])) ] @@ -38,7 +41,7 @@ key @scheme[k] and value @scheme[v], if a mapping from @scheme[k] to some value @scheme[(combine/key k v0 v)]. @defexamples[ -#:eval (eval/require 'racket/dict 'unstable/dict) +#:eval the-eval (dict-union '([1 . one]) '([2 . two]) '([3 . three])) (dict-union '([1 . (one uno)] [2 . (two dos)]) '([1 . (ein une)] [2 . (zwei deux)]) @@ -64,7 +67,7 @@ key @scheme[k] and value @scheme[v], if a mapping from @scheme[k] to some value @scheme[(combine/key k v0 v)]. @defexamples[ -#:eval (eval/require 'racket/dict 'unstable/dict) +#:eval the-eval (define d (make-hash)) d (dict-union! d '([1 . (one uno)] [2 . (two dos)])) @@ -76,3 +79,5 @@ d ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/exn.scrbl b/collects/unstable/scribblings/exn.scrbl index d4a4335f20..225d05e289 100644 --- a/collects/unstable/scribblings/exn.scrbl +++ b/collects/unstable/scribblings/exn.scrbl @@ -1,9 +1,9 @@ #lang scribble/manual -@(require scribble/eval - "utils.rkt" - (for-label unstable/exn - racket/contract - racket/base)) +@(require scribble/eval "utils.rkt" + (for-label unstable/exn racket/contract racket/base)) + +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/exn)) @title[#:tag "exn"]{Exceptions} @@ -36,10 +36,12 @@ level before continuing. Exceptions raised by the final expression are not caught by @scheme[try]. @defexamples[ -#:eval (eval/require 'unstable/exn) +#:eval the-eval (try (+ 1 2) (+ 3 4)) (try (+ 'one 'two) (+ 3 4)) (try (+ 'one 'two) (+ 'three 'four)) ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/find.scrbl b/collects/unstable/scribblings/find.scrbl index 7b7c094833..ab73f0e3a6 100644 --- a/collects/unstable/scribblings/find.scrbl +++ b/collects/unstable/scribblings/find.scrbl @@ -1,16 +1,11 @@ #lang scribble/manual -@(require scribble/eval - "utils.rkt" - (for-label unstable/find - racket/contract - racket/shared - racket/base)) - -@title[#:tag "find"]{Find} +@(require scribble/eval "utils.rkt" + (for-label unstable/find racket/contract racket/shared racket/base)) @(define the-eval (make-base-eval)) -@(the-eval '(require unstable/find)) -@(the-eval '(require racket/shared)) +@(the-eval '(require unstable/find racket/shared)) + +@title[#:tag "find"]{Find} @defmodule[unstable/find] diff --git a/collects/unstable/scribblings/function.scrbl b/collects/unstable/scribblings/function.scrbl index f33d891589..322a3dde78 100644 --- a/collects/unstable/scribblings/function.scrbl +++ b/collects/unstable/scribblings/function.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/function)) +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/function)) + @title{Functions} @defmodule[unstable/function] @@ -23,7 +26,7 @@ Creates a function that ignores its inputs and evaluates the given body. Useful for creating event handlers with no (or irrelevant) arguments. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (thunk (define x 1) (printf "~a\n" x))) (f) (f 'x) @@ -41,7 +44,7 @@ Negates the results of @scheme[f]; equivalent to @scheme[(not (f x ...))]. This function is reprovided from @schememodname[scheme/function]. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (negate exact-integer?)) (f 1) (f 'one) @@ -55,7 +58,7 @@ Combines calls to each function with @scheme[and]. Equivalent to @scheme[(and (f x ...) ...)] @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (conjoin exact? integer?)) (f 1) (f 1.0) @@ -71,7 +74,7 @@ Combines calls to each function with @scheme[or]. Equivalent to @scheme[(or (f x ...) ...)] @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (disjoin exact? integer?)) (f 1) (f 1.0) @@ -89,7 +92,7 @@ Passes @scheme[x ...] to @scheme[f]. Keyword arguments are allowed. Equivalent to @scheme[(f x ...)]. Useful for application in higher-order contexts. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (map call (list + - * /) (list 1 2 3 4) @@ -121,7 +124,7 @@ equations: ] @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define reciprocal (papply / 1)) (reciprocal 3) (reciprocal 4) @@ -169,7 +172,7 @@ to @scheme[curryn] and @scheme[currynr] in the following manner: ] @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define reciprocal (curryn 1 / 1)) (reciprocal 3) @@ -211,7 +214,7 @@ This is useful for function expressions that may be run, but not called, before without evaluating @scheme[f]. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (eta g)) f (define g (lambda (x) (+ x 1))) @@ -230,7 +233,7 @@ This macro behaves similarly to @scheme[eta], but produces a function with statically known arity which may improve efficiency and error reporting. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define f (eta* g x)) f (procedure-arity f) @@ -256,7 +259,7 @@ argument @scheme[id] is @scheme[(param)]; @scheme[param] is bound to @scheme[id] via @scheme[parameterize] during the function call. @defexamples[ -#:eval (eval/require 'unstable/function) +#:eval the-eval (define p (open-output-string)) (define hello-world (lambda/parameter ([port #:param current-output-port]) @@ -267,3 +270,5 @@ via @scheme[parameterize] during the function call. ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/gui/notify.scrbl b/collects/unstable/scribblings/gui/notify.scrbl index a01f28353a..5cc39f274d 100644 --- a/collects/unstable/scribblings/gui/notify.scrbl +++ b/collects/unstable/scribblings/gui/notify.scrbl @@ -1,16 +1,13 @@ #lang scribble/manual -@(require scribble/eval - "../utils.rkt" - (for-label unstable/gui/notify - racket/contract - racket/class - racket/base)) - -@title[#:tag "gui-notify"]{Notify-boxes} +@(require scribble/eval "../utils.rkt" + (for-label racket/base unstable/gui/notify racket/contract + racket/class)) @(define the-eval (make-base-eval)) @(the-eval '(require racket/class unstable/private/notify)) +@title[#:tag "gui-notify"]{Notify-boxes} + @defmodule[unstable/gui/notify] @unstable[@author+email["Ryan Culpepper" "ryanc@racket-lang.org"]] diff --git a/collects/unstable/scribblings/hash.scrbl b/collects/unstable/scribblings/hash.scrbl index db8b749d19..d259bd7993 100644 --- a/collects/unstable/scribblings/hash.scrbl +++ b/collects/unstable/scribblings/hash.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label scheme unstable/hash)) +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/hash)) + @title{Hash Tables} @defmodule[unstable/hash] @@ -26,7 +29,7 @@ key @scheme[k] and value @scheme[v], if a mapping from @scheme[k] to some value @scheme[(combine/key k v0 v)]. @defexamples[ -#:eval (eval/require 'unstable/hash) +#:eval the-eval (hash-union (make-immutable-hash '([1 . one])) (make-immutable-hash '([2 . two])) (make-immutable-hash '([3 . three]))) (hash-union (make-immutable-hash '([1 . (one uno)] [2 . (two dos)])) (make-immutable-hash '([1 . (ein une)] [2 . (zwei deux)])) @@ -52,7 +55,7 @@ key @scheme[k] and value @scheme[v], if a mapping from @scheme[k] to some value @scheme[(combine/key k v0 v)]. @defexamples[ -#:eval (eval/require 'unstable/hash) +#:eval the-eval (define h (make-hash)) h (hash-union! h (make-immutable-hash '([1 . (one uno)] [2 . (two dos)]))) @@ -64,3 +67,5 @@ h ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/list.scrbl b/collects/unstable/scribblings/list.scrbl index c7378148b2..9307ae5c57 100644 --- a/collects/unstable/scribblings/list.scrbl +++ b/collects/unstable/scribblings/list.scrbl @@ -1,13 +1,7 @@ #lang scribble/doc -@(require scribble/base - scribble/manual - scribble/eval - "utils.rkt" - (for-label racket/dict - unstable/list - syntax/id-table - racket/contract - racket/base)) +@(require scribble/base scribble/manual scribble/eval "utils.rkt" + (for-label racket/base racket/dict syntax/id-table racket/contract + unstable/list)) @(define the-eval (make-base-eval)) @(the-eval '(require unstable/list)) @@ -75,7 +69,7 @@ Produces @racket[(values (filter f l) ...)]. @defproc[(extend [l1 list?] [l2 list?] [v any/c]) list?]{ Extends @racket[l2] to be as long as @racket[l1] by adding @racket[(- (length l1) (length l2))] copies of @racket[v] to the end of -@racket[l2]. +@racket[l2]. @examples[#:eval the-eval (extend '(1 2 3) '(a) 'b) @@ -115,7 +109,7 @@ true value. The procedures @racket[equal?], @racket[eqv?], and ] } - + @addition{Carl Eastlund} @defproc[(map/values [n natural-number/c] @@ -145,7 +139,7 @@ Produces a pair of lists of the respective values of @scheme[f] applied to the elements in @scheme[lst ...] sequentially. @defexamples[ -#:eval (eval/require 'unstable/list) +#:eval the-eval (map2 (lambda (x) (values (+ x 1) (- x 1))) (list 1 2 3)) ] diff --git a/collects/unstable/scribblings/logging.scrbl b/collects/unstable/scribblings/logging.scrbl index ab72c4356a..1f707d258c 100644 --- a/collects/unstable/scribblings/logging.scrbl +++ b/collects/unstable/scribblings/logging.scrbl @@ -1,12 +1,11 @@ #lang scribble/manual - @(require scribble/eval "utils.rkt" (for-label racket unstable/logging)) -@title{Logging} - @(define the-eval (make-base-eval)) @(the-eval '(require unstable/logging)) +@title{Logging} + @defmodule[unstable/logging] This module provides tools for logging. diff --git a/collects/unstable/scribblings/match.scrbl b/collects/unstable/scribblings/match.scrbl index 2874c67ae9..2922df4c25 100644 --- a/collects/unstable/scribblings/match.scrbl +++ b/collects/unstable/scribblings/match.scrbl @@ -1,13 +1,9 @@ #lang scribble/manual -@(require scribble/eval - "utils.rkt" - (for-label unstable/match - racket/match - racket/contract - racket/base)) +@(require scribble/eval "utils.rkt" + (for-label unstable/match racket/match racket/contract racket/base)) @(define the-eval (make-base-eval)) -@(the-eval '(require unstable/match racket/match)) +@(the-eval '(require racket/match unstable/match)) @title[#:tag "match"]{Match} @@ -42,7 +38,7 @@ Returns @scheme[#t] if the result of @scheme[val-expr] matches any of @scheme[pat], and returns @scheme[#f] otherwise. @defexamples[ -#:eval (eval/require 'racket/match 'unstable/match) +#:eval the-eval (match? (list 1 2 3) (list a b c) (vector x y z)) @@ -63,7 +59,7 @@ result value of @scheme[rhs-expr], and continues matching each subsequent @scheme[pat]. @defexamples[ -#:eval (eval/require 'racket/match 'unstable/match) +#:eval the-eval (match (list 1 2 3) [(as ([a 0]) (list b c d)) (list a b c d)]) ] diff --git a/collects/unstable/scribblings/mutated-vars.scrbl b/collects/unstable/scribblings/mutated-vars.scrbl index 7c6615c496..abd44919c6 100644 --- a/collects/unstable/scribblings/mutated-vars.scrbl +++ b/collects/unstable/scribblings/mutated-vars.scrbl @@ -7,11 +7,11 @@ syntax/id-table racket/base)) -@title[#:tag "mutated-vars"]{Finding Mutated Variables} - @(define the-eval (make-base-eval)) @(the-eval '(require unstable/mutated-vars syntax/id-table racket/dict)) +@title[#:tag "mutated-vars"]{Finding Mutated Variables} + @defmodule[unstable/mutated-vars] @unstable[@author+email["Sam Tobin-Hochstadt" "samth@ccs.neu.edu"]] diff --git a/collects/unstable/scribblings/port.scrbl b/collects/unstable/scribblings/port.scrbl index 53d86571c3..952c8f95ee 100644 --- a/collects/unstable/scribblings/port.scrbl +++ b/collects/unstable/scribblings/port.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/port)) +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/port)) + @title{Ports} @defmodule[unstable/port] @@ -18,7 +21,7 @@ This function produces a list of all the values produced by calling until it produces @scheme[eof]. @defexamples[ -#:eval (eval/require 'unstable/port) +#:eval the-eval (read-all read (open-input-string "1 2 3")) (parameterize ([current-input-port (open-input-string "a b c")]) (read-all)) @@ -36,7 +39,7 @@ is set to @scheme[port], up until it produces @scheme[eof]. The source location of the result spans the entire portion of the port that was read. @defexamples[ -#:eval (eval/require 'unstable/port) +#:eval the-eval (define port1 (open-input-string "1 2 3")) (port-count-lines! port1) (read-all-syntax read-syntax port1) @@ -59,7 +62,7 @@ missing fields. This function relies on @scheme[port-next-location], so line counting must be enabled for @scheme[port] to get meaningful results. @defexamples[ -#:eval (eval/require 'unstable/port) +#:eval the-eval (define port (open-input-string "1 2 3")) (port-count-lines! port) (read port) @@ -68,3 +71,5 @@ counting must be enabled for @scheme[port] to get meaningful results. ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/pretty.scrbl b/collects/unstable/scribblings/pretty.scrbl index 0883e9e22f..0b04dab43d 100644 --- a/collects/unstable/scribblings/pretty.scrbl +++ b/collects/unstable/scribblings/pretty.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/pretty)) +@(define the-eval (make-base-eval)) +@(the-eval '(require racket/pretty unstable/pretty)) + @title{Pretty-Printing} @defmodule[unstable/pretty] @@ -18,7 +21,7 @@ This module provides tools for pretty-printing. This procedure behaves like @scheme[pretty-format], but it formats values consistently with @scheme[write] instead of @scheme[print]. -@examples[#:eval (eval/require 'racket/pretty 'unstable/pretty) +@examples[#:eval the-eval (struct both [a b] #:transparent) (pretty-format/write (list (both (list 'a 'b) (list "a" "b")))) ] @@ -34,7 +37,7 @@ consistently with @scheme[write] instead of @scheme[print]. This procedure behaves like @scheme[pretty-format], but it formats values consistently with @scheme[display] instead of @scheme[print]. -@examples[#:eval (eval/require 'racket/pretty 'unstable/pretty) +@examples[#:eval the-eval (struct both [a b] #:transparent) (pretty-format/display (list (both (list 'a 'b) (list "a" "b")))) ] @@ -51,9 +54,11 @@ This procedure behaves the same as @scheme[pretty-format], but is named more explicitly to describe how it formats values. It is included for symmetry with @scheme[pretty-format/write] and @scheme[pretty-format/display]. -@examples[#:eval (eval/require 'racket/pretty 'unstable/pretty) +@examples[#:eval the-eval (struct both [a b] #:transparent) (pretty-format/print (list (both (list 'a 'b) (list "a" "b")))) ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/prop-contract.scrbl b/collects/unstable/scribblings/prop-contract.scrbl index 7691756ab7..a77f8ffcdf 100644 --- a/collects/unstable/scribblings/prop-contract.scrbl +++ b/collects/unstable/scribblings/prop-contract.scrbl @@ -1,11 +1,6 @@ #lang scribble/manual -@(require scribble/struct - scribble/decode - scribble/eval - "utils.rkt" - (for-label racket/base - racket/contract - unstable/prop-contract)) +@(require scribble/struct scribble/decode scribble/eval "utils.rkt" + (for-label racket/base racket/contract unstable/prop-contract)) @(define the-eval (make-base-eval)) @(the-eval '(require racket/contract unstable/prop-contract)) diff --git a/collects/unstable/scribblings/require.scrbl b/collects/unstable/scribblings/require.scrbl index b032fd47c1..ddc5d57984 100644 --- a/collects/unstable/scribblings/require.scrbl +++ b/collects/unstable/scribblings/require.scrbl @@ -1,6 +1,9 @@ #lang scribble/manual @(require scribble/eval "utils.rkt" (for-label racket unstable/require)) +@(define the-eval (make-base-eval)) +@(the-eval '(require unstable/require)) + @title{Requiring Modules} @defmodule[unstable/require] @@ -23,8 +26,10 @@ Re-exports all bindings provided by each @scheme[module-path]. Equivalent to: Produces the names exported by the @scheme[require-spec]s as a list of symbols. @examples[ -#:eval (eval/require 'unstable/require) +#:eval the-eval (quote-require racket/bool racket/function) ] } + +@(close-eval the-eval) diff --git a/collects/unstable/scribblings/sequence.scrbl b/collects/unstable/scribblings/sequence.scrbl index 7f58c4ef0f..af53cf95ec 100644 --- a/collects/unstable/scribblings/sequence.scrbl +++ b/collects/unstable/scribblings/sequence.scrbl @@ -1,9 +1,6 @@ #lang scribble/manual -@(require scribble/eval - "utils.rkt" - (for-label unstable/sequence - racket/contract - racket/base)) +@(require scribble/eval "utils.rkt" + (for-label racket/base unstable/sequence racket/contract)) @(define the-eval (make-base-eval)) @(the-eval '(require unstable/sequence)) @@ -12,7 +9,8 @@ [(_ id what) (t "An " (scheme id) " application can provide better performance for " (elem what) - " iteration when it appears directly in a " (scheme for) " clause.")])) + " iteration when it appears directly in a " (scheme for) + " clause.")])) @title[#:tag "sequence"]{Sequences} diff --git a/collects/unstable/scribblings/struct.scrbl b/collects/unstable/scribblings/struct.scrbl index 45da4dc08f..78a4115128 100644 --- a/collects/unstable/scribblings/struct.scrbl +++ b/collects/unstable/scribblings/struct.scrbl @@ -1,15 +1,12 @@ #lang scribble/manual -@(require scribble/eval - "utils.rkt" - (for-label unstable/struct - racket/contract - racket/base)) - -@title[#:tag "struct"]{Structs} +@(require scribble/eval "utils.rkt" + (for-label racket/base unstable/struct racket/contract)) @(define the-eval (make-base-eval)) @(the-eval '(require unstable/struct)) +@title[#:tag "struct"]{Structs} + @defmodule[unstable/struct] @unstable[@author+email["Ryan Culpepper" "ryanc@racket-lang.org"]] diff --git a/collects/unstable/scribblings/syntax.scrbl b/collects/unstable/scribblings/syntax.scrbl index 3bdf3b1557..308e6cc86f 100644 --- a/collects/unstable/scribblings/syntax.scrbl +++ b/collects/unstable/scribblings/syntax.scrbl @@ -1,16 +1,10 @@ #lang scribble/manual -@(require scribble/struct - scribble/decode - scribble/eval - "utils.rkt" - (for-label racket/base - racket/contract - syntax/kerncase +@(require scribble/struct scribble/decode scribble/eval "utils.rkt" + (for-label racket/base racket/contract syntax/kerncase unstable/syntax)) @(define the-eval (make-base-eval)) -@(the-eval '(require unstable/syntax)) -@(the-eval '(require (for-syntax racket/base unstable/syntax))) +@(the-eval '(require unstable/syntax (for-syntax racket/base unstable/syntax))) @title[#:tag "syntax"]{Syntax} @@ -69,7 +63,7 @@ This form constructs a list of syntax objects based on the given templates. It is equivalent to @scheme[(syntax->list (syntax (template ...)))]. @defexamples[ -#:eval (eval/require '(for-syntax racket/base unstable/syntax) 'unstable/syntax) +#:eval the-eval (with-syntax ([(x ...) (syntax (1 2 3))]) (syntax-list x ...)) ] } @@ -87,7 +81,7 @@ These produce the directory and file name, respectively, of the path with which with a path. @defexamples[ -#:eval (eval/require '(for-syntax racket/base unstable/syntax) 'unstable/syntax) +#:eval the-eval (define loc (list (build-path "/tmp" "dir" "somewhere.ss") #f #f #f #f)) diff --git a/collects/unstable/scribblings/utils.rkt b/collects/unstable/scribblings/utils.rkt index 7c7ce01705..714bc41085 100644 --- a/collects/unstable/scribblings/utils.rkt +++ b/collects/unstable/scribblings/utils.rkt @@ -2,14 +2,12 @@ (require scribble/base scribble/manual scribble/core scribble/eval) (provide unstable unstable-header - addition - eval/require) + addition) (define (unstable . authors) - (make-compound-paragraph - plain - (list (apply author authors) - (unstable-header)))) + (make-compound-paragraph plain + (list (apply author authors) + (unstable-header)))) (define (unstable-header) @para{This library is @emph{unstable}; @@ -18,9 +16,3 @@ (define (addition name) @margin-note{The subsequent bindings were added by @|name|.}) - -(define (eval/require . paths) - (let* ([e (make-base-eval)]) - (for ([path (in-list paths)]) - (e `(require ,path))) - e)) diff --git a/collects/unstable/scribblings/wrapc.scrbl b/collects/unstable/scribblings/wrapc.scrbl index b8e656948a..d9b21f1dc4 100644 --- a/collects/unstable/scribblings/wrapc.scrbl +++ b/collects/unstable/scribblings/wrapc.scrbl @@ -1,16 +1,9 @@ #lang scribble/manual -@(require scribble/struct - scribble/decode - scribble/eval - "utils.rkt" - (for-label racket/base - racket/contract - unstable/wrapc - racket/syntax)) +@(require scribble/struct scribble/decode scribble/eval "utils.rkt" + (for-label racket/base racket/contract unstable/wrapc racket/syntax)) -@(begin - (define the-eval (make-base-eval)) - (the-eval '(require racket/contract (for-syntax racket/base unstable/wrapc)))) +@(define the-eval (make-base-eval)) +@(the-eval '(require racket/contract (for-syntax racket/base unstable/wrapc))) @title[#:tag "wrapc"]{Contracts for macro subexpressions}