diff --git a/collects/compiler/decompile.ss b/collects/compiler/decompile.ss index be61752ce8..c1d5f9cd77 100644 --- a/collects/compiler/decompile.ss +++ b/collects/compiler/decompile.ss @@ -207,9 +207,9 @@ ,@(map (lambda (lam) (decompile-lam lam globs stack closed)) lams))] - [(struct let-one (rhs body flonum?)) + [(struct let-one (rhs body flonum? unused?)) (let ([id (or (extract-id rhs) - (gensym 'local))]) + (gensym (if unused? 'unused 'local)))]) `(let ([,id ,(let ([v (decompile-expr rhs globs (cons id stack) closed)]) (if flonum? (list '#%as-flonum v) diff --git a/collects/compiler/zo-marshal.ss b/collects/compiler/zo-marshal.ss index 2ac973aba1..a174d35642 100644 --- a/collects/compiler/zo-marshal.ss +++ b/collects/compiler/zo-marshal.ss @@ -160,7 +160,7 @@ [(struct case-lam (name lams)) (traverse-data name visit) (for-each (lambda (lam) (traverse-lam lam visit)) lams)] - [(struct let-one (rhs body flonum?)) + [(struct let-one (rhs body flonum? unused?)) (traverse-expr rhs visit) (traverse-expr body visit)] [(struct let-void (count boxes? body)) @@ -297,7 +297,8 @@ CPT_PATH CPT_CLOSURE CPT_DELAY_REF - CPT_PREFAB) + CPT_PREFAB + CPT_LET_ONE_UNUSED) (define-enum 0 @@ -314,7 +315,7 @@ APPVALS_EXPD SPLICE_EXPD) -(define CPT_SMALL_NUMBER_START 35) +(define CPT_SMALL_NUMBER_START 36) (define CPT_SMALL_NUMBER_END 60) (define CPT_SMALL_SYMBOL_START 60) @@ -715,8 +716,12 @@ (cons (or name null) lams) out)] - [(struct let-one (rhs body flonum?)) - (out-byte (if flonum? CPT_LET_ONE_FLONUM CPT_LET_ONE) out) + [(struct let-one (rhs body flonum? unused?)) + (out-byte (cond + [flonum? CPT_LET_ONE_FLONUM] + [unused? CPT_LET_ONE_UNUSED] + [else CPT_LET_ONE]) + out) (out-expr (protect-quote rhs) out) (out-expr (protect-quote body) out)] [(struct let-void (count boxes? body)) diff --git a/collects/compiler/zo-parse.ss b/collects/compiler/zo-parse.ss index 868d7cbff2..37c3dcd2d6 100644 --- a/collects/compiler/zo-parse.ss +++ b/collects/compiler/zo-parse.ss @@ -412,7 +412,8 @@ [32 closure] [33 delayed] [34 prefab] - [35 60 small-number] + [35 let-one-unused] + [36 60 small-number] [60 80 small-symbol] [80 92 small-marshalled] [92 ,(+ 92 small-list-max) small-proper-list] @@ -766,9 +767,10 @@ (if ppr null (read-compact cp))) (read-compact-list l ppr cp)) (loop l ppr)))] - [(let-one let-one-flonum) + [(let-one let-one-flonum let-one-unused) (make-let-one (read-compact cp) (read-compact cp) - (eq? cpt-tag 'let-one-flonum))] + (eq? cpt-tag 'let-one-flonum) + (eq? cpt-tag 'let-one-unused))] [(branch) (make-branch (read-compact cp) (read-compact cp) (read-compact cp))] [(module-index) (module-path-index-join (read-compact cp) (read-compact cp))] diff --git a/collects/compiler/zo-structs.ss b/collects/compiler/zo-structs.ss index cd37ba4a5a..a1f8f982a8 100644 --- a/collects/compiler/zo-structs.ss +++ b/collects/compiler/zo-structs.ss @@ -118,7 +118,7 @@ (define-form-struct (closure expr) ([code lam?] [gen-id symbol?])) ; a static closure (nothing to close over) (define-form-struct (case-lam expr) ([name (or/c symbol? vector? empty?)] [clauses (listof (or/c lam? indirect?))])) ; each clause is a lam (added indirect) -(define-form-struct (let-one expr) ([rhs (or/c expr? seq? indirect? any/c)] [body (or/c expr? seq? indirect? any/c)] [flonum? boolean?])) ; pushes one value onto stack +(define-form-struct (let-one expr) ([rhs (or/c expr? seq? indirect? any/c)] [body (or/c expr? seq? indirect? any/c)] [flonum? boolean?] [unused? boolean?])) ; pushes one value onto stack (define-form-struct (let-void expr) ([count exact-nonnegative-integer?] [boxes? boolean?] [body (or/c expr? seq? indirect? any/c)])) ; create new stack slots (define-form-struct (install-value expr) ([count exact-nonnegative-integer?] [pos exact-nonnegative-integer?] diff --git a/collects/rico/rico.ss b/collects/rico/rico.ss index 9fa1f54ab7..7944b04dfb 100644 --- a/collects/rico/rico.ss +++ b/collects/rico/rico.ss @@ -106,6 +106,6 @@ (printf "\nA command can be specified by an unambigous prefix.") (unless show-all? (printf "\nSee `rico --help' for a complete list of commands.")) - (printf "\nSee `rico --help' for help on a command.")) - (newline) - (exit 1)) + (printf "\nSee `rico --help' for help on a command.") + (newline) + (exit (if show-all? 0 1)))) diff --git a/collects/scribble/scheme.ss b/collects/scribble/scheme.ss index be6e34538a..9e18e73634 100644 --- a/collects/scribble/scheme.ss +++ b/collects/scribble/scheme.ss @@ -160,7 +160,23 @@ e)))) (make-element style content))) - (define (typeset-atom c out color? quote-depth) + (define (to-quoted qs qq? quote-depth out color? inc!) + (if (and qq? (zero? quote-depth)) + (begin + (out qs (and color? value-color)) + (inc!) + (add1 quote-depth)) + quote-depth)) + + (define (to-unquoted qq? quote-depth out color? inc!) + (if (or (not qq?) (zero? quote-depth)) + quote-depth + (begin + (out "," (and color? meta-color)) + (inc!) + (to-unquoted qq? (sub1 quote-depth) out color? inc!)))) + + (define (typeset-atom c out color? quote-depth qq?) (if (and (var-id? (syntax-e c)) (zero? quote-depth)) (out (format "~s" (let ([v (var-id-sym (syntax-e c))]) @@ -185,48 +201,56 @@ is-var?))) (values (substring s 1) #t #f) (values s #f #f))))]) - (if (or (element? (syntax-e c)) - (delayed-element? (syntax-e c)) - (part-relative-element? (syntax-e c))) - (out (syntax-e c) #f) - (out (if (and (identifier? c) - color? - (quote-depth . <= . 0) - (not (or it? is-var?))) - (if (pair? (identifier-label-binding c)) - (make-id-element c s) - s) - (literalize-spaces s)) - (cond - [(positive? quote-depth) value-color] - [(let ([v (syntax-e c)]) - (or (number? v) - (string? v) - (bytes? v) - (char? v) - (regexp? v) - (byte-regexp? v) - (boolean? v))) - value-color] - [(identifier? c) + (let ([quote-depth (if (and qq? (identifier? c)) + (let ([quote-depth + (if (and (quote-depth . < . 2) + (memq (syntax-e c) '(unquote unquote-splicing))) + (to-unquoted qq? quote-depth out color? void) + quote-depth)]) + (to-quoted "'" qq? quote-depth out color? void)) + quote-depth)]) + (if (or (element? (syntax-e c)) + (delayed-element? (syntax-e c)) + (part-relative-element? (syntax-e c))) + (out (syntax-e c) #f) + (out (if (and (identifier? c) + color? + (quote-depth . <= . 0) + (not (or it? is-var?))) + (if (pair? (identifier-label-binding c)) + (make-id-element c s) + s) + (literalize-spaces s)) (cond - [is-var? - variable-color] - [(and (identifier? c) - (memq (syntax-e c) (current-keyword-list))) - keyword-color] - [(and (identifier? c) - (memq (syntax-e c) (current-meta-list))) - meta-color] - [it? variable-color] - [else symbol-color])] - [else paren-color]) - (string-length s)))))) + [(positive? quote-depth) value-color] + [(let ([v (syntax-e c)]) + (or (number? v) + (string? v) + (bytes? v) + (char? v) + (regexp? v) + (byte-regexp? v) + (boolean? v))) + value-color] + [(identifier? c) + (cond + [is-var? + variable-color] + [(and (identifier? c) + (memq (syntax-e c) (current-keyword-list))) + keyword-color] + [(and (identifier? c) + (memq (syntax-e c) (current-meta-list))) + meta-color] + [it? variable-color] + [else symbol-color])] + [else paren-color]) + (string-length s))))))) (define omitable (make-style #f '(omitable))) - (define (gen-typeset c multi-line? prefix1 prefix suffix color?) - (let* ([c (syntax-ize c 0)] + (define (gen-typeset c multi-line? prefix1 prefix suffix color? qq?) + (let* ([c (syntax-ize c 0 #:qq? qq?)] [content null] [docs null] [first (syntax-case c (code:line) @@ -234,6 +258,7 @@ [else c])] [init-col (or (syntax-column first) 0)] [src-col init-col] + [inc-src-col (lambda () (set! src-col (add1 src-col)))] [dest-col 0] [highlight? #f] [col-map (make-hash)] @@ -314,7 +339,7 @@ (set! src-col c) (hash-set! next-col-map src-col dest-col)))] [(c init-line!) (advance c init-line! 0)])) - (define (convert-infix c quote-depth) + (define (convert-infix c quote-depth qq?) (let ([l (syntax->list c)]) (and l ((length l) . >= . 3) @@ -340,7 +365,7 @@ (if val? value-color #f) (list (make-element/cache (if val? value-color paren-color) '". ") - (typeset a #f "" "" "" (not val?)) + (typeset a #f "" "" "" (not val?) qq?) (make-element/cache (if val? value-color paren-color) '" .")) (+ (syntax-span a) 4))) (list (syntax-source a) @@ -358,7 +383,7 @@ (cond [(eq? s 'rsquo) "'"] [else s])) - (define (loop init-line! quote-depth) + (define (loop init-line! quote-depth qq?) (lambda (c) (cond [(eq? 'code:blank (syntax-e c)) @@ -394,12 +419,13 @@ (set! src-col s-col) (set! dest-col 0) (out "; " comment-color)) - 0) + 0 + qq?) l))] [(and (pair? (syntax-e c)) (eq? (syntax-e (car (syntax-e c))) 'code:line)) (let ([l (cdr (syntax->list c))]) - (for-each (loop init-line! quote-depth) + (for-each (loop init-line! quote-depth qq?) l))] [(and (pair? (syntax-e c)) (eq? (syntax-e (car (syntax-e c))) 'code:hilite)) @@ -411,59 +437,67 @@ (set! src-col (syntax-column (cadr l))) (hash-set! next-col-map src-col dest-col) (set! highlight? #t) - ((loop init-line! quote-depth) (cadr l)) + ((loop init-line! quote-depth qq?) (cadr l)) (set! highlight? h?) (set! src-col (add1 src-col)))] [(and (pair? (syntax-e c)) (eq? (syntax-e (car (syntax-e c))) 'code:quote)) (advance c init-line!) - (out "(" (if (positive? quote-depth) value-color paren-color)) - (set! src-col (+ src-col 1)) - (hash-set! next-col-map src-col dest-col) - ((loop init-line! quote-depth) - (datum->syntax #'here 'quote (car (syntax-e c)))) - (for-each (loop init-line! (add1 quote-depth)) - (cdr (syntax->list c))) - (out ")" (if (positive? quote-depth) value-color paren-color)) - (set! src-col (+ src-col 1)) - #; - (hash-set! next-col-map src-col dest-col)] + (let ([quote-depth (to-quoted "`" qq? quote-depth out color? inc-src-col)]) + (out "(" (if (positive? quote-depth) value-color paren-color)) + (set! src-col (+ src-col 1)) + (hash-set! next-col-map src-col dest-col) + ((loop init-line! quote-depth qq?) + (datum->syntax #'here 'quote (car (syntax-e c)))) + (for-each (loop init-line! (add1 quote-depth) qq?) + (cdr (syntax->list c))) + (out ")" (if (positive? quote-depth) value-color paren-color)) + (set! src-col (+ src-col 1)) + #; + (hash-set! next-col-map src-col dest-col))] [(and (pair? (syntax-e c)) (memq (syntax-e (car (syntax-e c))) '(quote quasiquote unquote unquote-splicing quasisyntax syntax unsyntax unsyntax-splicing)) (let ([v (syntax->list c)]) - (and v (= 2 (length v))))) + (and v (= 2 (length v)))) + (or (not qq?) + (quote-depth . > . 1) + (not (memq (syntax-e (car (syntax-e c))) + '(unquote unquote-splicing))))) (advance c init-line!) - (let-values ([(str quote-delta) - (case (syntax-e (car (syntax-e c))) - [(quote) (values "'" +inf.0)] - [(unquote) (values "," -1)] - [(unquote-splicing) (values ",@" -1)] - [(quasiquote) (values "`" +1)] - [(syntax) (values "#'" 0)] - [(quasisyntax) (values "#`" 0)] - [(unsyntax) (values "#," 0)] - [(unsyntax-splicing) (values "#,@" 0)])]) - (out str (if (positive? (+ quote-depth quote-delta)) - value-color - reader-color)) - (let ([i (cadr (syntax->list c))]) - (set! src-col (or (syntax-column i) src-col)) - (hash-set! next-col-map src-col dest-col) - ((loop init-line! (+ quote-depth quote-delta)) i)))] + (let ([quote-depth (to-quoted "`" qq? quote-depth out color? inc-src-col)]) + (let-values ([(str quote-delta) + (case (syntax-e (car (syntax-e c))) + [(quote) (values "'" +inf.0)] + [(unquote) (values "," -1)] + [(unquote-splicing) (values ",@" -1)] + [(quasiquote) (values "`" +1)] + [(syntax) (values "#'" 0)] + [(quasisyntax) (values "#`" 0)] + [(unsyntax) (values "#," 0)] + [(unsyntax-splicing) (values "#,@" 0)])]) + (out str (if (positive? (+ quote-depth quote-delta)) + value-color + reader-color)) + (let ([i (cadr (syntax->list c))]) + (set! src-col (or (syntax-column i) src-col)) + (hash-set! next-col-map src-col dest-col) + ((loop init-line! (+ quote-depth quote-delta) qq?) i))))] [(and (pair? (syntax-e c)) - (convert-infix c quote-depth)) + (convert-infix c quote-depth qq?)) => (lambda (converted) - ((loop init-line! quote-depth) converted))] + ((loop init-line! quote-depth qq?) converted))] [(or (pair? (syntax-e c)) (null? (syntax-e c)) (vector? (syntax-e c)) (and (struct? (syntax-e c)) - (prefab-struct-key (syntax-e c)))) + (prefab-struct-key (syntax-e c))) + (struct-proxy? (syntax-e c))) (let* ([sh (or (syntax-property c 'paren-shape) #\()] - [quote-depth (if (and (zero? quote-depth) + [quote-depth (if (and (not qq?) + (zero? quote-depth) (or (vector? (syntax-e c)) (struct? (syntax-e c)))) +inf.0 @@ -474,87 +508,101 @@ opt-color paren-color))]) (advance c init-line!) - (when (vector? (syntax-e c)) - (let ([vec (syntax-e c)]) - (out "#" #;(format "#~a" (vector-length vec)) p-color) - (if (zero? (vector-length vec)) - (set! src-col (+ src-col (- (syntax-span c) 2))) - (set! src-col (+ src-col (- (syntax-column (vector-ref vec 0)) - (syntax-column c) - 1)))))) - (when (struct? (syntax-e c)) - (out "#s" p-color) - (set! src-col (+ src-col 2))) - (out (case sh - [(#\[ #\?) "["] - [(#\{) "{"] - [else "("]) - p-color) - (set! src-col (+ src-col 1)) - (hash-set! next-col-map src-col dest-col) - (let lloop ([l (cond - [(vector? (syntax-e c)) - (vector->short-list (syntax-e c) syntax-e)] - [(struct? (syntax-e c)) - (let ([l (vector->list (struct->vector (syntax-e c)))]) - ;; Need to build key datum, syntax-ize it internally, and - ;; set the overall width to fit right: - (cons (let ([key (syntax-ize (prefab-struct-key (syntax-e c)) - (+ 3 (or (syntax-column c) 0)) - (or (syntax-line c) 1))] - [end (if (pair? (cdr l)) - (and (equal? (syntax-line c) (syntax-line (cadr l))) - (syntax-column (cadr l))) - (and (syntax-column c) - (+ (syntax-column c) (syntax-span c))))]) - (if end - (datum->syntax #f - (syntax-e key) - (vector #f (syntax-line key) - (syntax-column key) - (syntax-position key) - (- end 1 (syntax-column key)))) - end)) - (cdr l)))] - [else c])]) - (cond - [(and (syntax? l) - (pair? (syntax-e l)) - (not (and (memq (syntax-e (car (syntax-e l))) - '(quote unquote syntax unsyntax quasiquote quasiunsyntax)) - (let ([v (syntax->list l)]) - (and v (= 2 (length v))))))) - (lloop (syntax-e l))] - [(or (null? l) - (and (syntax? l) - (null? (syntax-e l)))) - (void)] - [(pair? l) - ((loop init-line! quote-depth) (car l)) - (lloop (cdr l))] - [else - (advance l init-line! -2) - (out ". " (if (positive? quote-depth) value-color paren-color)) - (set! src-col (+ src-col 3)) + (let ([quote-depth (if (struct-proxy? (syntax-e c)) + (to-unquoted qq? quote-depth out color? inc-src-col) + (to-quoted "`" qq? quote-depth out color? inc-src-col))]) + (when (vector? (syntax-e c)) + (let ([vec (syntax-e c)]) + (out "#" #;(format "#~a" (vector-length vec)) p-color) + (if (zero? (vector-length vec)) + (set! src-col (+ src-col (- (syntax-span c) 2))) + (set! src-col (+ src-col (- (syntax-column (vector-ref vec 0)) + (syntax-column c) + 1)))))) + (when (struct? (syntax-e c)) + (out "#s" p-color) + (set! src-col (+ src-col 2))) + (out (case sh + [(#\[ #\?) "["] + [(#\{) "{"] + [else "("]) + p-color) + (set! src-col (+ src-col 1)) (hash-set! next-col-map src-col dest-col) - ((loop init-line! quote-depth) l)])) - (out (case sh - [(#\[ #\?) "]"] - [(#\{) "}"] - [else ")"]) - p-color) - (set! src-col (+ src-col 1)) - #; - (hash-set! next-col-map src-col dest-col))] + (let lloop ([l (cond + [(vector? (syntax-e c)) + (vector->short-list (syntax-e c) syntax-e)] + [(struct? (syntax-e c)) + (let ([l (vector->list (struct->vector (syntax-e c)))]) + ;; Need to build key datum, syntax-ize it internally, and + ;; set the overall width to fit right: + (cons (let ([key (syntax-ize (prefab-struct-key (syntax-e c)) + (+ 3 (or (syntax-column c) 0)) + (or (syntax-line c) 1))] + [end (if (pair? (cdr l)) + (and (equal? (syntax-line c) (syntax-line (cadr l))) + (syntax-column (cadr l))) + (and (syntax-column c) + (+ (syntax-column c) (syntax-span c))))]) + (if end + (datum->syntax #f + (syntax-e key) + (vector #f (syntax-line key) + (syntax-column key) + (syntax-position key) + (- end 1 (syntax-column key)))) + end)) + (cdr l)))] + [(struct-proxy? (syntax-e c)) + (cons + (struct-proxy-name (syntax-e c)) + (struct-proxy-content (syntax-e c)))] + [else c])] + [first-qq? (and qq? (not (struct-proxy? (syntax-e c))))]) + (cond + [(and (syntax? l) + (pair? (syntax-e l)) + (not (and (memq (syntax-e (car (syntax-e l))) + '(quote unquote syntax unsyntax quasiquote quasiunsyntax)) + (let ([v (syntax->list l)]) + (and v (= 2 (length v)))) + (or (not qq?) + (quote-depth . > . 1) + (not (memq (syntax-e (car (syntax-e l))) + '(unquote unquote-splicing))))))) + (lloop (syntax-e l) first-qq?)] + [(or (null? l) + (and (syntax? l) + (null? (syntax-e l)))) + (void)] + [(pair? l) + ((loop init-line! quote-depth first-qq?) (car l)) + (lloop (cdr l) qq?)] + [else + (advance l init-line! -2) + (out ". " (if (positive? quote-depth) value-color paren-color)) + (set! src-col (+ src-col 3)) + (hash-set! next-col-map src-col dest-col) + ((loop init-line! quote-depth first-qq?) l)])) + (out (case sh + [(#\[ #\?) "]"] + [(#\{) "}"] + [else ")"]) + p-color) + (set! src-col (+ src-col 1)) + #; + (hash-set! next-col-map src-col dest-col)))] [(box? (syntax-e c)) (advance c init-line!) - (out "#&" value-color) - (set! src-col (+ src-col 2)) - (hash-set! next-col-map src-col dest-col) - ((loop init-line! +inf.0) (unbox (syntax-e c)))] + (let ([quote-depth (to-quoted "`" qq? quote-depth out color? inc-src-col)]) + (out "#&" value-color) + (set! src-col (+ src-col 2)) + (hash-set! next-col-map src-col dest-col) + ((loop init-line! (if qq? quote-depth +inf.0) qq?) (unbox (syntax-e c))))] [(hash? (syntax-e c)) (advance c init-line!) - (let ([equal-table? (not (hash-eq? (syntax-e c)))]) + (let ([equal-table? (not (hash-eq? (syntax-e c)))] + [quote-depth (to-quoted "`" qq? quote-depth out color? inc-src-col)]) (out (if equal-table? "#hash" "#hasheq") @@ -563,7 +611,7 @@ [orig-col src-col]) (set! src-col (+ src-col delta)) (hash-set! next-col-map src-col dest-col) - ((loop init-line! +inf.0) + ((loop init-line! (if qq? quote-depth +inf.0) qq?) (syntax-ize (hash-map (syntax-e c) cons) (+ (syntax-column c) delta))) (set! src-col (+ orig-col (syntax-span c)))))] @@ -582,17 +630,17 @@ value-color paren-color)) (set! src-col (+ src-col 3)) - ((loop init-line! quote-depth) (graph-defn-r (syntax-e c))))] + ((loop init-line! quote-depth qq?) (graph-defn-r (syntax-e c))))] [else (advance c init-line!) - (typeset-atom c out color? quote-depth) + (typeset-atom c out color? quote-depth qq?) (set! src-col (+ src-col (or (syntax-span c) 1))) #; (hash-set! next-col-map src-col dest-col)]))) (out prefix1 #f) (set! dest-col 0) (hash-set! next-col-map init-col dest-col) - ((loop (lambda () (set! src-col init-col) (set! dest-col 0)) 0) c) + ((loop (lambda () (set! src-col init-col) (set! dest-col 0)) 0 qq?) c) (if (list? suffix) (map (lambda (sfx) (finish-line!) @@ -607,8 +655,8 @@ (make-table block-color (map list (reverse docs)))) (make-sized-element #f (reverse content) dest-col)))) - (define (typeset c multi-line? prefix1 prefix suffix color?) - (let* ([c (syntax-ize c 0)] + (define (typeset c multi-line? prefix1 prefix suffix color? qq?) + (let* ([c (syntax-ize c 0 #:qq? qq?)] [s (syntax-e c)]) (if (or multi-line? (eq? 'code:blank s) @@ -620,7 +668,7 @@ (hash? s) (graph-defn? s) (graph-reference? s)) - (gen-typeset c multi-line? prefix1 prefix suffix color?) + (gen-typeset c multi-line? prefix1 prefix suffix color? qq?) (typeset-atom c (letrec ([mk (case-lambda @@ -632,19 +680,19 @@ (make-element/cache (and color? color) elem) (make-sized-element (and color? color) elem len))])]) mk) - color? 0)))) + color? 0 qq?)))) - (define (to-element c) - (typeset c #f "" "" "" #t)) + (define (to-element c #:qq? [qq? #f]) + (typeset c #f "" "" "" #t qq?)) - (define (to-element/no-color c) - (typeset c #f "" "" "" #f)) + (define (to-element/no-color c #:qq? [qq? #f]) + (typeset c #f "" "" "" #f qq?)) - (define (to-paragraph c) - (typeset c #t "" "" "" #t)) + (define (to-paragraph c #:qq? [qq? #f]) + (typeset c #t "" "" "" #t qq?)) - (define ((to-paragraph/prefix pfx1 pfx sfx) c) - (typeset c #t pfx1 pfx sfx #t)) + (define ((to-paragraph/prefix pfx1 pfx sfx) c #:qq? [qq? #f]) + (typeset c #t pfx1 pfx sfx #t qq?)) (begin-for-syntax (define-struct variable-id (sym) @@ -760,12 +808,13 @@ (define-struct just-context (val ctx)) (define-struct alternate-display (id string)) (define-struct literal-syntax (stx)) + (define-struct struct-proxy (name content)) (define-struct graph-reference (bx)) (define-struct graph-defn (r bx)) - (define (syntax-ize v col [line 1]) - (do-syntax-ize v col line (box #hasheq()) #f)) + (define (syntax-ize v col [line 1] #:qq? [qq? #f]) + (do-syntax-ize v col line (box #hasheq()) #f (and qq? 0))) (define (graph-count ht graph?) (and graph? @@ -773,23 +822,23 @@ (set-box! ht (hash-set (unbox ht) '#%graph-count (add1 n))) n))) - (define (do-syntax-ize v col line ht graph?) + (define (do-syntax-ize v col line ht graph? qq) (cond [((syntax-ize-hook) v col) => (lambda (r) r)] [(shaped-parens? v) - (syntax-property (do-syntax-ize (shaped-parens-val v) col line ht #f) + (syntax-property (do-syntax-ize (shaped-parens-val v) col line ht #f qq) 'paren-shape (shaped-parens-shape v))] [(just-context? v) - (let ([s (do-syntax-ize (just-context-val v) col line ht #f)]) + (let ([s (do-syntax-ize (just-context-val v) col line ht #f qq)]) (datum->syntax (just-context-ctx v) (syntax-e s) s s (just-context-ctx v)))] [(alternate-display? v) - (let ([s (do-syntax-ize (alternate-display-id v) col line ht #f)]) + (let ([s (do-syntax-ize (alternate-display-id v) col line ht #f qq)]) (syntax-property s 'display-string (alternate-display-string v)))] @@ -802,23 +851,38 @@ (vector #f line col (+ 1 col) 1)))] [(and (list? v) (pair? v) - (memq (let ([s (car v)]) - (if (just-context? s) - (just-context-val s) - s)) - '(quote unquote unquote-splicing))) - (let ([c (do-syntax-ize (cadr v) (+ col 1) line ht #f)]) - (datum->syntax #f - (list (do-syntax-ize (car v) col line ht #f) - c) - (vector #f line col (+ 1 col) - (+ 1 (syntax-span c)))))] + (let ([s (let ([s (car v)]) + (if (just-context? s) + (just-context-val s) + s))]) + (and + (or (memq s '(quaisquote quote)) + (and (memq s '(unquote unquote-splicing)) + (or (not qq) + (qq . > . 2)))) + s))) + => (lambda (s) + (let ([c (do-syntax-ize (cadr v) (+ col 1) line ht #f qq)]) + (datum->syntax #f + (list (do-syntax-ize (car v) col line ht #f + (and qq + (case s + [(quaisquote) (add1 qq)] + [(unquote unquote-splicing) (sub1 qq)] + [else qq]))) + c) + (vector #f line col (+ 1 col) + (+ 1 (syntax-span c))))))] [(or (list? v) (vector? v) (and (struct? v) - (prefab-struct-key v))) + (or (and qq + ;; Watch out for partially transparent subtypes of `element': + (not (element? v))) + (prefab-struct-key v)))) (let ([orig-ht (unbox ht)] - [graph-box (box (graph-count ht graph?))]) + [graph-box (box (graph-count ht graph?))] + [qq (and qq (max 1 qq))]) (set-box! ht (hash-set (unbox ht) v graph-box)) (let* ([graph-sz (if graph? (+ 2 (string-length (format "~a" (unbox graph-box)))) @@ -826,26 +890,35 @@ [vec-sz (cond [(vector? v) (+ 1 #;(string-length (format "~a" (vector-length v))))] - [(struct? v) 2] + [(struct? v) + (if (prefab-struct-key v) + 2 + 0)] [else 0])] [r (let ([l (let loop ([col (+ col 1 vec-sz graph-sz)] [v (cond [(vector? v) (vector->short-list v values)] [(struct? v) - (cons (prefab-struct-key v) + (cons (let ([pf (prefab-struct-key v)]) + (if pf + (prefab-struct-key v) + (object-name v))) (cdr (vector->list (struct->vector v))))] [else v])]) (if (null? v) null - (let ([i (do-syntax-ize (car v) col line ht #f)]) + (let ([i (do-syntax-ize (car v) col line ht #f qq)]) (cons i (loop (+ col 1 (syntax-span i)) (cdr v))))))]) (datum->syntax #f (cond [(vector? v) (short-list->vector v l)] [(struct? v) - (apply make-prefab-struct (prefab-struct-key v) (cdr l))] + (let ([pf (prefab-struct-key v)]) + (if pf + (apply make-prefab-struct (prefab-struct-key v) (cdr l)) + (make-struct-proxy (car l) (cdr l))))] [else l]) (vector #f line (+ graph-sz col) @@ -868,22 +941,23 @@ [(unbox graph-box) ;; Go again, this time knowing that there will be a graph: (set-box! ht orig-ht) - (do-syntax-ize v col line ht #t)] + (do-syntax-ize v col line ht #t qq)] [else r])))] [(pair? v) (let ([orig-ht (unbox ht)] - [graph-box (box (graph-count ht graph?))]) + [graph-box (box (graph-count ht graph?))] + [qq (and qq (max 1 qq))]) (set-box! ht (hash-set (unbox ht) v graph-box)) (let* ([inc (if graph? (+ 2 (string-length (format "~a" (unbox graph-box)))) 0)] - [a (do-syntax-ize (car v) (+ col 1 inc) line ht #f)] + [a (do-syntax-ize (car v) (+ col 1 inc) line ht #f qq)] [sep (if (and (pair? (cdr v)) ;; FIXME: what if it turns out to be a graph reference? (not (hash-ref (unbox ht) (cdr v) #f))) 0 3)] - [b (do-syntax-ize (cdr v) (+ col 1 inc (syntax-span a) sep) line ht #f)]) + [b (do-syntax-ize (cdr v) (+ col 1 inc (syntax-span a) sep) line ht #f qq)]) (let ([r (datum->syntax #f (cons a b) (vector #f line (+ col inc) (+ 1 col inc) @@ -898,10 +972,10 @@ [(unbox graph-box) ;; Go again... (set-box! ht orig-ht) - (do-syntax-ize v col line ht #t)] + (do-syntax-ize v col line ht #t qq)] [else r]))))] [(box? v) - (let ([a (do-syntax-ize (unbox v) (+ col 2) line ht #f)]) + (let ([a (do-syntax-ize (unbox v) (+ col 2) line ht #f (and qq (max 1 qq)))]) (datum->syntax #f (box a) (vector #f line col (+ 1 col) diff --git a/collects/scribblings/mzc/decompile.scrbl b/collects/scribblings/mzc/decompile.scrbl index 0cdcd6b2fa..b3adc4e6df 100644 --- a/collects/scribblings/mzc/decompile.scrbl +++ b/collects/scribblings/mzc/decompile.scrbl @@ -41,6 +41,13 @@ Many forms in the decompiled code, such as @scheme[module], @schemeidfont{#%sfs-clear}, which indicates that the variable-stack location holding the variable will be cleared to prevent the variable's value from being retained by the garbage collector. + Variables whose name starts with @schemeidfont{unused} are never + actually stored on the stack, and so they never have + @schemeidfont{#%sfs-clear} annotations. (The bytecode compiler + normally eliminates such bindings, but sometimes it cannot, either + because it cannot prove that the right-hand side produces the right + number of values, or the discovery that the variable is unused + happens too late with the compiler.) Mutable variables are converted to explicitly boxed values using @schemeidfont{#%box}, @schemeidfont{#%unbox}, and diff --git a/collects/scribblings/mzc/zo-parse.scrbl b/collects/scribblings/mzc/zo-parse.scrbl index 189e1f2b56..bf7afef207 100644 --- a/collects/scribblings/mzc/zo-parse.scrbl +++ b/collects/scribblings/mzc/zo-parse.scrbl @@ -347,13 +347,17 @@ arguments given.} @defstruct+[(let-one expr) ([rhs (or/c expr? seq? indirect? any/c)] [body (or/c expr? seq? indirect? any/c)] - [flonum? boolean?])]{ + [flonum? boolean?] + [unused? boolean?])]{ Pushes an uninitialized slot onto the stack, evaluates @scheme[rhs] and puts its value into the slot, and then runs @scheme[body]. If @scheme[flonum?] is @scheme[#t], then @scheme[rhs] must produce a flonum, and the slot must be accessed by @scheme[localref]s that -expect a flonum. +expect a flonum. If @scheme[unused?] is @scheme[#t], then the slot +must not be used, and the value of @scheme[rhs] is not actually pushed +onto the stack (but @scheme[rhs] is constrained to produce a single +value). After @scheme[rhs] is evaluated, the stack is restored to its depth from before evaluating @scheme[rhs]. Note that the new slot is created diff --git a/collects/scribblings/reference/struct.scrbl b/collects/scribblings/reference/struct.scrbl index 951c6d9aab..87dd20b8e6 100644 --- a/collects/scribblings/reference/struct.scrbl +++ b/collects/scribblings/reference/struct.scrbl @@ -429,8 +429,13 @@ does not match the size of the @scheme[struct] if more than one field is inaccessible.)} @defproc[(struct? [v any/c]) any]{ Returns @scheme[#t] if - @scheme[struct->vector] exposes any fields of @scheme[v] with the - current inspector, @scheme[#f] otherwise.} + @scheme[struct-info] exposes any structure types of @scheme[v] with + the current inspector, @scheme[#f] otherwise. + + Typically, when @scheme[(struct? v)] is true, then + @scheme[(struct->vector v)] exposes at least one field value. It is + possible, however, for the only visible types of @scheme[v] to + contribute zero fields.} @defproc[(struct-type? [v any/c]) boolean?]{Returns @scheme[#t] if @scheme[v] is a structure type descriptor value, @scheme[#f] diff --git a/collects/scribblings/scribble/manual.scrbl b/collects/scribblings/scribble/manual.scrbl index a62f9b345c..8736312ca5 100644 --- a/collects/scribblings/scribble/manual.scrbl +++ b/collects/scribblings/scribble/manual.scrbl @@ -112,6 +112,13 @@ A few other escapes are recognized symbolically: @item{@schemeidfont{code:blank} typesets as a blank space.} + @item{@scheme[(#,(scheme code:hilite) _datum)] typesets like + @scheme[_datum], but with a background highlight.} + + @item{@scheme[(#,(scheme code:quote) _datum)] typesets like + @scheme[(@#,schemeidfont{quote} _datum)], but without rendering the + @schemeidfont{quote} as @litchar{'}.} + @item{@schemeidfont{_}@scheme[_id] typesets as @scheme[id], but colored as a variable (like @scheme[schemevarfont]); this escape applies only if @schemeidfont{_}@scheme[_id] has no diff --git a/collects/scribblings/scribble/reader-internals.scrbl b/collects/scribblings/scribble/reader-internals.scrbl index 9e0240e15b..4086e29de7 100644 --- a/collects/scribblings/scribble/reader-internals.scrbl +++ b/collects/scribblings/scribble/reader-internals.scrbl @@ -149,7 +149,7 @@ is an example of this. @defmodulelang[at-exp]{The @schememodname[at-exp] language installs @"@"-reader support in the readtable, and then chains to the reader of -another language that is specified immediate after +another language that is specified immediately after @schememodname[at-exp].} For example, @scheme[@#,hash-lang[] at-exp scheme/base] adds @"@"-reader diff --git a/collects/scribblings/scribble/scheme.scrbl b/collects/scribblings/scribble/scheme.scrbl index 4f98ff2b50..9285fecf62 100644 --- a/collects/scribblings/scribble/scheme.scrbl +++ b/collects/scribblings/scribble/scheme.scrbl @@ -41,7 +41,7 @@ The @scheme[stx-prop-expr] should produce a procedure for recording a @scheme[id] has such a property. The default is @scheme[syntax-property].} -@defproc[(to-paragraph [v any/c]) block?]{ +@defproc[(to-paragraph [v any/c] [#:qq? qq? any/c #f]) block?]{ Typesets an S-expression that is represented by a syntax object, where source-location information in the syntax object controls the @@ -50,18 +50,26 @@ generated layout. Identifiers that have @scheme[for-label] bindings are typeset and hyperlinked based on definitions declared elsewhere (via @scheme[defproc], @scheme[defform], etc.). The identifiers -@schemeidfont{code:line}, @schemeidfont{code:comment}, and -@schemeidfont{code:blank} are handled as in @scheme[schemeblock], as +@schemeidfont{code:line}, @schemeidfont{code:comment}, +@schemeidfont{code:blank}, @schemeidfont{code:hilite}, and +@schemeidfont{code:quote} are handled as in @scheme[schemeblock], as are identifiers that start with @litchar{_}. In addition, the given @scheme[v] can contain @scheme[var-id], @scheme[shaped-parens], @scheme[just-context], or @scheme[literal-syntax] structures to be typeset specially (see each structure type for details), or it can contain @scheme[element] -structures that are used directly in the output.} +structures that are used directly in the output. + +If @scheme[qq?] is true, then @scheme[v] is rendered ``quasiquote'' +style, much like @scheme[print] with the @scheme[print-as-quasiquote] +parameter set to @scheme[#t]. In that case, @scheme[for-label] +bindings on identifiers are ignored, since the identifiers are all +quoted in the output. Typically, @scheme[qq?] is set to true for +printing result values.} -@defproc[((to-paragraph/prefix [prefix1 any/c] [prefix any/c] [suffix any/c]) +@defproc[((to-paragraph/prefix [prefix1 any/c] [prefix any/c] [suffix any/c] [#:qq? qq? any/c #f]) [v any/c]) block?]{ @@ -73,13 +81,13 @@ first line, @scheme[prefix] is prefix to any subsequent line, and it is added to the end on its own line.} -@defproc[(to-element [v any/c]) element?]{ +@defproc[(to-element [v any/c] [#:qq? qq? any/c #f]) element?]{ Like @scheme[to-paragraph], except that source-location information is mostly ignored, since the result is meant to be inlined into a paragraph.} -@defproc[(to-element/no-color [v any/c]) element?]{ +@defproc[(to-element/no-color [v any/c] [#:qq? qq? any/c #f]) element?]{ Like @scheme[to-element], but @scheme[for-syntax] bindings are ignored, and the generated text is uncolored. This variant is diff --git a/src/mzscheme/src/cstartup.inc b/src/mzscheme/src/cstartup.inc index 34bcfefb2b..bd81f14a01 100644 --- a/src/mzscheme/src/cstartup.inc +++ b/src/mzscheme/src/cstartup.inc @@ -1,5 +1,5 @@ { - SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,53,50,0,0,0,1,0,0,3,0,12,0, + SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,54,50,0,0,0,1,0,0,3,0,12,0, 16,0,21,0,28,0,41,0,48,0,53,0,58,0,62,0,69,0,72,0,78, 0,92,0,106,0,109,0,115,0,119,0,121,0,132,0,134,0,148,0,155,0, 177,0,179,0,193,0,4,1,33,1,44,1,55,1,65,1,101,1,134,1,167, @@ -14,98 +14,98 @@ 115,61,120,73,108,101,116,114,101,99,45,118,97,108,117,101,115,66,108,97,109, 98,100,97,1,20,112,97,114,97,109,101,116,101,114,105,122,97,116,105,111,110, 45,107,101,121,61,118,73,100,101,102,105,110,101,45,118,97,108,117,101,115,97, -35,11,8,240,35,76,0,0,95,159,2,15,35,35,159,2,14,35,35,159,2, -14,35,35,16,20,2,3,2,1,2,5,2,1,2,7,2,1,2,6,2,1, +36,11,8,240,44,76,0,0,95,159,2,15,36,36,159,2,14,36,36,159,2, +14,36,36,16,20,2,3,2,1,2,5,2,1,2,7,2,1,2,6,2,1, 2,8,2,1,2,9,2,1,2,10,2,1,2,4,2,1,2,11,2,1,2, -12,2,1,97,36,11,8,240,35,76,0,0,93,159,2,14,35,36,16,2,2, -2,161,2,1,36,2,2,2,1,2,2,96,11,11,8,240,35,76,0,0,16, -0,96,37,11,8,240,35,76,0,0,16,0,13,16,4,35,29,11,11,2,1, +12,2,1,97,37,11,8,240,44,76,0,0,93,159,2,14,36,37,16,2,2, +2,161,2,1,37,2,2,2,1,2,2,96,11,11,8,240,44,76,0,0,16, +0,96,38,11,8,240,44,76,0,0,16,0,13,16,4,36,29,11,11,2,1, 11,18,16,2,99,64,104,101,114,101,8,31,8,30,8,29,8,28,8,27,93, -8,224,42,76,0,0,95,9,8,224,42,76,0,0,2,1,27,248,22,142,4, -195,249,22,135,4,80,158,38,35,251,22,80,2,16,248,22,95,199,12,249,22, -70,2,17,248,22,97,201,27,248,22,142,4,195,249,22,135,4,80,158,38,35, +8,224,51,76,0,0,95,9,8,224,51,76,0,0,2,1,27,248,22,142,4, +195,249,22,135,4,80,158,39,36,251,22,80,2,16,248,22,95,199,12,249,22, +70,2,17,248,22,97,201,27,248,22,142,4,195,249,22,135,4,80,158,39,36, 251,22,80,2,16,248,22,95,199,249,22,70,2,17,248,22,97,201,12,27,248, -22,72,248,22,142,4,196,28,248,22,78,193,20,15,159,36,35,36,28,248,22, -78,248,22,72,194,248,22,71,193,249,22,135,4,80,158,38,35,251,22,80,2, +22,72,248,22,142,4,196,28,248,22,78,193,20,15,159,37,36,37,28,248,22, +78,248,22,72,194,248,22,71,193,249,22,135,4,80,158,39,36,251,22,80,2, 16,248,22,71,199,249,22,70,2,10,248,22,72,201,11,18,16,2,101,10,8, 31,8,30,8,29,8,28,8,27,16,4,11,11,2,18,3,1,8,101,110,118, -49,50,54,56,56,16,4,11,11,2,19,3,1,8,101,110,118,49,50,54,56, -57,93,8,224,43,76,0,0,95,9,8,224,43,76,0,0,2,1,27,248,22, -72,248,22,142,4,196,28,248,22,78,193,20,15,159,36,35,36,28,248,22,78, -248,22,72,194,248,22,71,193,249,22,135,4,80,158,38,35,250,22,80,2,20, +49,50,54,57,51,16,4,11,11,2,19,3,1,8,101,110,118,49,50,54,57, +52,93,8,224,52,76,0,0,95,9,8,224,52,76,0,0,2,1,27,248,22, +72,248,22,142,4,196,28,248,22,78,193,20,15,159,37,36,37,28,248,22,78, +248,22,72,194,248,22,71,193,249,22,135,4,80,158,39,36,250,22,80,2,20, 248,22,80,249,22,80,248,22,80,2,21,248,22,71,201,251,22,80,2,16,2, 21,2,21,249,22,70,2,12,248,22,72,204,18,16,2,101,11,8,31,8,30, 8,29,8,28,8,27,16,4,11,11,2,18,3,1,8,101,110,118,49,50,54, -57,49,16,4,11,11,2,19,3,1,8,101,110,118,49,50,54,57,50,93,8, -224,44,76,0,0,95,9,8,224,44,76,0,0,2,1,248,22,142,4,193,27, +57,54,16,4,11,11,2,19,3,1,8,101,110,118,49,50,54,57,55,93,8, +224,53,76,0,0,95,9,8,224,53,76,0,0,2,1,248,22,142,4,193,27, 248,22,142,4,194,249,22,70,248,22,80,248,22,71,196,248,22,72,195,27,248, -22,72,248,22,142,4,23,197,1,249,22,135,4,80,158,38,35,28,248,22,55, -248,22,136,4,248,22,71,23,198,2,27,249,22,2,32,0,89,162,8,44,36, -42,9,222,33,39,248,22,142,4,248,22,95,23,200,2,250,22,80,2,22,248, +22,72,248,22,142,4,23,197,1,249,22,135,4,80,158,39,36,28,248,22,55, +248,22,136,4,248,22,71,23,198,2,27,249,22,2,32,0,89,162,8,44,37, +43,9,222,33,39,248,22,142,4,248,22,95,23,200,2,250,22,80,2,22,248, 22,80,249,22,80,248,22,80,248,22,71,23,204,2,250,22,81,2,23,249,22, 2,22,71,23,204,2,248,22,97,23,206,2,249,22,70,248,22,71,23,202,1, 249,22,2,22,95,23,200,1,250,22,81,2,20,249,22,2,32,0,89,162,8, -44,36,46,9,222,33,40,248,22,142,4,248,22,71,201,248,22,72,198,27,248, +44,37,47,9,222,33,40,248,22,142,4,248,22,71,201,248,22,72,198,27,248, 22,142,4,194,249,22,70,248,22,80,248,22,71,196,248,22,72,195,27,248,22, -72,248,22,142,4,23,197,1,249,22,135,4,80,158,38,35,250,22,81,2,22, -249,22,2,32,0,89,162,8,44,36,46,9,222,33,42,248,22,142,4,248,22, +72,248,22,142,4,23,197,1,249,22,135,4,80,158,39,36,250,22,81,2,22, +249,22,2,32,0,89,162,8,44,37,47,9,222,33,42,248,22,142,4,248,22, 71,201,248,22,72,198,27,248,22,72,248,22,142,4,196,27,248,22,142,4,248, -22,71,195,249,22,135,4,80,158,39,35,28,248,22,78,195,250,22,81,2,20, +22,71,195,249,22,135,4,80,158,40,36,28,248,22,78,195,250,22,81,2,20, 9,248,22,72,199,250,22,80,2,3,248,22,80,248,22,71,199,250,22,81,2, 9,248,22,72,201,248,22,72,202,27,248,22,72,248,22,142,4,23,197,1,27, 249,22,1,22,84,249,22,2,22,142,4,248,22,142,4,248,22,71,199,249,22, -135,4,80,158,39,35,251,22,80,1,22,119,105,116,104,45,99,111,110,116,105, +135,4,80,158,40,36,251,22,80,1,22,119,105,116,104,45,99,111,110,116,105, 110,117,97,116,105,111,110,45,109,97,114,107,2,24,250,22,81,1,23,101,120, 116,101,110,100,45,112,97,114,97,109,101,116,101,114,105,122,97,116,105,111,110, 21,95,1,27,99,111,110,116,105,110,117,97,116,105,111,110,45,109,97,114,107, 45,115,101,116,45,102,105,114,115,116,11,2,24,201,250,22,81,2,20,9,248, -22,72,203,27,248,22,72,248,22,142,4,196,28,248,22,78,193,20,15,159,36, -35,36,249,22,135,4,80,158,38,35,27,248,22,142,4,248,22,71,197,28,249, +22,72,203,27,248,22,72,248,22,142,4,196,28,248,22,78,193,20,15,159,37, +36,37,249,22,135,4,80,158,39,36,27,248,22,142,4,248,22,71,197,28,249, 22,175,8,62,61,62,248,22,136,4,248,22,95,196,250,22,80,2,20,248,22, 80,249,22,80,21,93,2,25,248,22,71,199,250,22,81,2,4,249,22,80,2, 25,249,22,80,248,22,104,203,2,25,248,22,72,202,251,22,80,2,16,28,249, 22,175,8,248,22,136,4,248,22,71,200,64,101,108,115,101,10,248,22,71,197, 250,22,81,2,20,9,248,22,72,200,249,22,70,2,4,248,22,72,202,100,8, 31,8,30,8,29,8,28,8,27,16,4,11,11,2,18,3,1,8,101,110,118, -49,50,55,49,52,16,4,11,11,2,19,3,1,8,101,110,118,49,50,55,49, -53,93,8,224,45,76,0,0,18,16,2,158,94,10,64,118,111,105,100,8,47, -95,9,8,224,45,76,0,0,2,1,27,248,22,72,248,22,142,4,196,249,22, -135,4,80,158,38,35,28,248,22,55,248,22,136,4,248,22,71,197,250,22,80, +49,50,55,49,57,16,4,11,11,2,19,3,1,8,101,110,118,49,50,55,50, +48,93,8,224,54,76,0,0,18,16,2,158,94,10,64,118,111,105,100,8,47, +95,9,8,224,54,76,0,0,2,1,27,248,22,72,248,22,142,4,196,249,22, +135,4,80,158,39,36,28,248,22,55,248,22,136,4,248,22,71,197,250,22,80, 2,26,248,22,80,248,22,71,199,248,22,95,198,27,248,22,136,4,248,22,71, 197,250,22,80,2,26,248,22,80,248,22,71,197,250,22,81,2,23,248,22,72, -199,248,22,72,202,159,35,20,105,159,35,16,1,11,16,0,83,158,41,20,103, -144,69,35,37,109,105,110,45,115,116,120,2,1,11,11,11,10,35,80,158,35, -35,20,105,159,35,16,0,16,0,16,1,2,2,36,16,0,35,16,0,35,11, -11,38,35,11,11,11,16,10,2,3,2,4,2,5,2,6,2,7,2,8,2, +199,248,22,72,202,159,36,20,105,159,36,16,1,11,16,0,83,158,42,20,103, +144,69,35,37,109,105,110,45,115,116,120,2,1,11,11,11,10,36,80,158,36, +36,20,105,159,36,16,0,16,0,16,1,2,2,37,16,0,36,16,0,36,11, +11,39,36,11,11,11,16,10,2,3,2,4,2,5,2,6,2,7,2,8,2, 9,2,10,2,11,2,12,16,10,11,11,11,11,11,11,11,11,11,11,16,10, -2,3,2,4,2,5,2,6,2,7,2,8,2,9,2,10,2,11,2,12,35, -45,36,11,11,11,16,0,16,0,16,0,35,35,11,11,11,11,16,0,16,0, -16,0,35,35,16,11,16,5,2,2,20,15,159,35,35,35,35,20,105,159,35, -16,0,16,1,33,32,10,16,5,2,5,89,162,8,44,36,52,9,223,0,33, -33,35,20,105,159,35,16,1,2,2,16,0,11,16,5,2,8,89,162,8,44, -36,52,9,223,0,33,34,35,20,105,159,35,16,1,2,2,16,0,11,16,5, -2,10,89,162,8,44,36,52,9,223,0,33,35,35,20,105,159,35,16,1,2, -2,16,1,33,36,11,16,5,2,12,89,162,8,44,36,55,9,223,0,33,37, -35,20,105,159,35,16,1,2,2,16,1,33,38,11,16,5,2,3,89,162,8, -44,36,57,9,223,0,33,41,35,20,105,159,35,16,1,2,2,16,0,11,16, -5,2,11,89,162,8,44,36,52,9,223,0,33,43,35,20,105,159,35,16,1, -2,2,16,0,11,16,5,2,9,89,162,8,44,36,53,9,223,0,33,44,35, -20,105,159,35,16,1,2,2,16,0,11,16,5,2,6,89,162,8,44,36,54, -9,223,0,33,45,35,20,105,159,35,16,1,2,2,16,0,11,16,5,2,4, -89,162,8,44,36,57,9,223,0,33,46,35,20,105,159,35,16,1,2,2,16, -1,33,48,11,16,5,2,7,89,162,8,44,36,53,9,223,0,33,49,35,20, -105,159,35,16,1,2,2,16,0,11,16,0,94,2,14,2,15,93,2,14,9, -9,35,0}; +2,3,2,4,2,5,2,6,2,7,2,8,2,9,2,10,2,11,2,12,36, +46,37,11,11,11,16,0,16,0,16,0,36,36,11,11,11,11,16,0,16,0, +16,0,36,36,16,11,16,5,2,2,20,15,159,36,36,36,36,20,105,159,36, +16,0,16,1,33,32,10,16,5,2,5,89,162,8,44,37,53,9,223,0,33, +33,36,20,105,159,36,16,1,2,2,16,0,11,16,5,2,8,89,162,8,44, +37,53,9,223,0,33,34,36,20,105,159,36,16,1,2,2,16,0,11,16,5, +2,10,89,162,8,44,37,53,9,223,0,33,35,36,20,105,159,36,16,1,2, +2,16,1,33,36,11,16,5,2,12,89,162,8,44,37,56,9,223,0,33,37, +36,20,105,159,36,16,1,2,2,16,1,33,38,11,16,5,2,3,89,162,8, +44,37,58,9,223,0,33,41,36,20,105,159,36,16,1,2,2,16,0,11,16, +5,2,11,89,162,8,44,37,53,9,223,0,33,43,36,20,105,159,36,16,1, +2,2,16,0,11,16,5,2,9,89,162,8,44,37,54,9,223,0,33,44,36, +20,105,159,36,16,1,2,2,16,0,11,16,5,2,6,89,162,8,44,37,55, +9,223,0,33,45,36,20,105,159,36,16,1,2,2,16,0,11,16,5,2,4, +89,162,8,44,37,58,9,223,0,33,46,36,20,105,159,36,16,1,2,2,16, +1,33,48,11,16,5,2,7,89,162,8,44,37,54,9,223,0,33,49,36,20, +105,159,36,16,1,2,2,16,0,11,16,0,94,2,14,2,15,93,2,14,9, +9,36,0}; EVAL_ONE_SIZED_STR((char *)expr, 2018); } { - SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,53,64,0,0,0,1,0,0,13,0,18,0, + SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,54,64,0,0,0,1,0,0,13,0,18,0, 35,0,50,0,68,0,84,0,94,0,112,0,132,0,148,0,166,0,197,0,226, 0,248,0,6,1,12,1,26,1,31,1,41,1,49,1,77,1,109,1,115,1, 160,1,205,1,229,1,12,2,14,2,180,2,14,4,55,4,128,5,214,5,44, 6,143,6,227,6,240,6,105,7,207,7,219,7,69,9,83,9,228,9,213,10, 195,11,202,11,210,11,218,11,87,12,101,12,86,14,188,14,210,14,226,14,174, -16,21,17,35,17,117,18,54,20,63,20,72,20,98,20,209,20,0,0,201,23, +16,21,17,35,17,117,18,54,20,63,20,72,20,98,20,209,20,0,0,202,23, 0,0,72,112,97,116,104,45,115,116,114,105,110,103,63,64,98,115,98,115,76, 110,111,114,109,97,108,45,99,97,115,101,45,112,97,116,104,74,45,99,104,101, 99,107,45,114,101,108,112,97,116,104,77,45,99,104,101,99,107,45,99,111,108, @@ -131,31 +131,31 @@ 103,6,21,21,115,116,114,105,110,103,32,111,114,32,98,121,116,101,32,115,116, 114,105,110,103,6,36,36,99,97,110,110,111,116,32,97,100,100,32,97,32,115, 117,102,102,105,120,32,116,111,32,97,32,114,111,111,116,32,112,97,116,104,58, -32,5,0,27,20,14,159,80,159,36,50,37,250,80,159,39,51,37,249,22,27, -11,80,159,41,50,37,22,144,13,10,248,22,167,5,23,196,2,28,248,22,164, -6,23,194,2,12,87,94,248,22,181,8,23,194,1,27,20,14,159,80,159,37, -50,37,250,80,159,40,51,37,249,22,27,11,80,159,42,50,37,22,144,13,10, +32,5,0,27,20,14,159,80,159,37,51,38,250,80,159,40,52,38,249,22,27, +11,80,159,42,51,38,22,144,13,10,248,22,167,5,23,196,2,28,248,22,164, +6,23,194,2,12,87,94,248,22,181,8,23,194,1,27,20,14,159,80,159,38, +51,38,250,80,159,41,52,38,249,22,27,11,80,159,43,51,38,22,144,13,10, 248,22,167,5,23,197,2,28,248,22,164,6,23,194,2,12,87,94,248,22,181, -8,23,194,1,27,20,14,159,80,159,38,50,37,250,80,159,41,51,37,249,22, -27,11,80,159,43,50,37,22,144,13,10,248,22,167,5,23,198,2,28,248,22, -164,6,23,194,2,12,87,94,248,22,181,8,23,194,1,248,80,159,39,53,36, +8,23,194,1,27,20,14,159,80,159,39,51,38,250,80,159,42,52,38,249,22, +27,11,80,159,44,51,38,22,144,13,10,248,22,167,5,23,198,2,28,248,22, +164,6,23,194,2,12,87,94,248,22,181,8,23,194,1,248,80,159,40,54,37, 197,28,248,22,78,23,195,2,9,27,248,22,71,23,196,2,27,28,248,22,128, 14,23,195,2,23,194,1,28,248,22,191,13,23,195,2,249,22,129,14,23,196, -1,250,80,158,42,48,248,22,144,14,2,19,11,10,250,80,158,40,48,248,22, +1,250,80,158,43,49,248,22,144,14,2,19,11,10,250,80,158,41,49,248,22, 144,14,2,19,23,197,1,10,28,23,193,2,249,22,70,248,22,131,14,249,22, 129,14,23,198,1,247,22,145,14,27,248,22,72,23,200,1,28,248,22,78,23, 194,2,9,27,248,22,71,23,195,2,27,28,248,22,128,14,23,195,2,23,194, -1,28,248,22,191,13,23,195,2,249,22,129,14,23,196,1,250,80,158,47,48, -248,22,144,14,2,19,11,10,250,80,158,45,48,248,22,144,14,2,19,23,197, +1,28,248,22,191,13,23,195,2,249,22,129,14,23,196,1,250,80,158,48,49, +248,22,144,14,2,19,11,10,250,80,158,46,49,248,22,144,14,2,19,23,197, 1,10,28,23,193,2,249,22,70,248,22,131,14,249,22,129,14,23,198,1,247, -22,145,14,248,80,159,45,52,36,248,22,72,23,199,1,87,94,23,193,1,248, -80,159,43,52,36,248,22,72,23,197,1,87,94,23,193,1,27,248,22,72,23, +22,145,14,248,80,159,46,53,37,248,22,72,23,199,1,87,94,23,193,1,248, +80,159,44,53,37,248,22,72,23,197,1,87,94,23,193,1,27,248,22,72,23, 198,1,28,248,22,78,23,194,2,9,27,248,22,71,23,195,2,27,28,248,22, 128,14,23,195,2,23,194,1,28,248,22,191,13,23,195,2,249,22,129,14,23, -196,1,250,80,158,45,48,248,22,144,14,2,19,11,10,250,80,158,43,48,248, +196,1,250,80,158,46,49,248,22,144,14,2,19,11,10,250,80,158,44,49,248, 22,144,14,2,19,23,197,1,10,28,23,193,2,249,22,70,248,22,131,14,249, -22,129,14,23,198,1,247,22,145,14,248,80,159,43,52,36,248,22,72,23,199, -1,248,80,159,41,52,36,248,22,72,196,27,248,22,168,13,23,195,2,28,23, +22,129,14,23,198,1,247,22,145,14,248,80,159,44,53,37,248,22,72,23,199, +1,248,80,159,42,53,37,248,22,72,196,27,248,22,168,13,23,195,2,28,23, 193,2,192,87,94,23,193,1,28,248,22,169,6,23,195,2,27,248,22,190,13, 195,28,192,192,248,22,191,13,195,11,87,94,28,28,248,22,169,13,23,195,2, 10,28,248,22,168,13,23,195,2,10,28,248,22,169,6,23,195,2,28,248,22, @@ -172,7 +172,7 @@ 28,249,22,157,14,0,22,35,114,120,34,91,47,92,92,93,91,46,32,93,43, 91,47,92,92,93,42,36,34,23,201,2,23,199,1,250,22,163,14,0,19,35, 114,120,34,91,32,46,93,43,40,91,47,92,92,93,42,41,36,34,23,202,1, -6,2,2,92,49,80,159,43,36,37,2,20,28,248,22,169,6,194,248,22,176, +6,2,2,92,49,80,159,44,37,38,2,20,28,248,22,169,6,194,248,22,176, 13,194,193,87,94,28,28,248,22,168,13,23,195,2,10,28,248,22,169,6,23, 195,2,28,248,22,190,13,23,195,2,10,248,22,191,13,23,195,2,11,12,250, 22,145,9,23,196,2,2,21,23,197,2,28,248,22,190,13,23,195,2,12,248, @@ -185,12 +185,12 @@ 28,248,22,169,6,23,195,2,28,248,22,190,13,23,195,2,10,248,22,191,13, 23,195,2,11,12,250,22,145,9,195,2,21,23,197,2,28,248,22,190,13,23, 195,2,12,248,22,184,11,249,22,190,10,248,22,134,7,250,22,153,7,2,22, -199,23,201,1,247,22,23,249,22,3,89,162,8,44,36,49,9,223,2,33,34, +199,23,201,1,247,22,23,249,22,3,89,162,8,44,37,50,9,223,2,33,34, 196,87,94,28,28,248,22,168,13,23,194,2,10,28,248,22,169,6,23,194,2, 28,248,22,190,13,23,194,2,10,248,22,191,13,23,194,2,11,12,250,22,145, 9,2,6,2,21,23,196,2,28,248,22,190,13,23,194,2,12,248,22,184,11, 249,22,190,10,248,22,134,7,250,22,153,7,2,22,2,6,23,200,1,247,22, -23,32,37,89,162,8,44,39,54,2,23,222,33,38,28,248,22,78,23,197,2, +23,32,37,89,162,8,44,40,55,2,23,222,33,38,28,248,22,78,23,197,2, 87,94,23,196,1,248,22,184,11,249,22,159,11,251,22,153,7,2,24,2,6, 28,248,22,78,23,203,2,87,94,23,202,1,23,201,1,250,22,1,22,186,13, 23,204,1,23,205,1,23,200,1,247,22,23,27,249,22,186,13,248,22,71,23, @@ -200,8 +200,8 @@ 193,10,28,248,22,169,6,193,28,248,22,190,13,193,10,248,22,191,13,193,11, 12,250,22,145,9,2,6,2,21,195,28,248,22,190,13,193,12,248,22,184,11, 249,22,190,10,248,22,134,7,250,22,153,7,2,22,2,6,199,247,22,23,249, -22,3,32,0,89,162,8,44,36,48,9,222,33,36,195,27,247,22,146,14,251, -2,37,196,197,198,196,32,40,89,162,43,41,58,2,23,222,33,41,28,248,22, +22,3,32,0,89,162,8,44,37,49,9,222,33,36,195,27,247,22,146,14,251, +2,37,196,197,198,196,32,40,89,162,44,42,59,2,23,222,33,41,28,248,22, 78,23,199,2,87,94,23,198,1,248,23,196,1,251,22,153,7,2,24,23,199, 1,28,248,22,78,23,203,2,87,94,23,202,1,23,201,1,250,22,1,22,186, 13,23,204,1,23,205,1,23,198,1,27,249,22,186,13,248,22,71,23,202,2, @@ -222,41 +222,41 @@ 72,200,27,247,22,146,14,253,2,40,198,199,200,201,202,198,87,95,28,28,248, 22,169,13,23,194,2,10,28,248,22,168,13,23,194,2,10,28,248,22,169,6, 23,194,2,28,248,22,190,13,23,194,2,10,248,22,191,13,23,194,2,11,12, -252,22,145,9,23,200,2,2,25,35,23,198,2,23,199,2,28,28,248,22,169, +252,22,145,9,23,200,2,2,25,36,23,198,2,23,199,2,28,28,248,22,169, 6,23,195,2,10,248,22,157,7,23,195,2,87,94,23,194,1,12,252,22,145, -9,23,200,2,2,26,36,23,198,2,23,199,1,91,159,38,11,90,161,38,35, +9,23,200,2,2,26,37,23,198,2,23,199,1,91,159,39,11,90,161,39,36, 11,248,22,189,13,23,197,2,87,94,23,195,1,87,94,28,192,12,250,22,146, -9,23,201,1,2,27,23,199,1,249,22,7,194,195,91,159,37,11,90,161,37, -35,11,87,95,28,28,248,22,169,13,23,196,2,10,28,248,22,168,13,23,196, +9,23,201,1,2,27,23,199,1,249,22,7,194,195,91,159,38,11,90,161,38, +36,11,87,95,28,28,248,22,169,13,23,196,2,10,28,248,22,168,13,23,196, 2,10,28,248,22,169,6,23,196,2,28,248,22,190,13,23,196,2,10,248,22, -191,13,23,196,2,11,12,252,22,145,9,2,9,2,25,35,23,200,2,23,201, +191,13,23,196,2,11,12,252,22,145,9,2,9,2,25,36,23,200,2,23,201, 2,28,28,248,22,169,6,23,197,2,10,248,22,157,7,23,197,2,12,252,22, -145,9,2,9,2,26,36,23,200,2,23,201,2,91,159,38,11,90,161,38,35, +145,9,2,9,2,26,37,23,200,2,23,201,2,91,159,39,11,90,161,39,36, 11,248,22,189,13,23,199,2,87,94,23,195,1,87,94,28,192,12,250,22,146, 9,2,9,2,27,23,201,2,249,22,7,194,195,27,249,22,178,13,250,22,162, 14,0,20,35,114,120,35,34,40,63,58,91,46,93,91,94,46,93,42,124,41, 36,34,248,22,174,13,23,201,1,28,248,22,169,6,23,203,2,249,22,181,7, 23,204,1,8,63,23,202,1,28,248,22,169,13,23,199,2,248,22,170,13,23, 199,1,87,94,23,198,1,247,22,171,13,28,248,22,168,13,194,249,22,186,13, -195,194,192,91,159,37,11,90,161,37,35,11,87,95,28,28,248,22,169,13,23, +195,194,192,91,159,38,11,90,161,38,36,11,87,95,28,28,248,22,169,13,23, 196,2,10,28,248,22,168,13,23,196,2,10,28,248,22,169,6,23,196,2,28, 248,22,190,13,23,196,2,10,248,22,191,13,23,196,2,11,12,252,22,145,9, -2,10,2,25,35,23,200,2,23,201,2,28,28,248,22,169,6,23,197,2,10, -248,22,157,7,23,197,2,12,252,22,145,9,2,10,2,26,36,23,200,2,23, -201,2,91,159,38,11,90,161,38,35,11,248,22,189,13,23,199,2,87,94,23, +2,10,2,25,36,23,200,2,23,201,2,28,28,248,22,169,6,23,197,2,10, +248,22,157,7,23,197,2,12,252,22,145,9,2,10,2,26,37,23,200,2,23, +201,2,91,159,39,11,90,161,39,36,11,248,22,189,13,23,199,2,87,94,23, 195,1,87,94,28,192,12,250,22,146,9,2,10,2,27,23,201,2,249,22,7, 194,195,27,249,22,178,13,249,22,167,7,250,22,163,14,0,9,35,114,120,35, 34,91,46,93,34,248,22,174,13,23,203,1,6,1,1,95,28,248,22,169,6, 23,202,2,249,22,181,7,23,203,1,8,63,23,201,1,28,248,22,169,13,23, 199,2,248,22,170,13,23,199,1,87,94,23,198,1,247,22,171,13,28,248,22, -168,13,194,249,22,186,13,195,194,192,249,247,22,136,5,194,11,249,80,159,37, -46,36,9,9,249,80,159,37,46,36,195,9,27,247,22,148,14,249,80,158,38, -47,28,23,195,2,27,248,22,186,7,6,11,11,80,76,84,67,79,76,76,69, +168,13,194,249,22,186,13,195,194,192,249,247,22,136,5,194,11,249,80,159,38, +47,37,9,9,249,80,159,38,47,37,195,9,27,247,22,148,14,249,80,158,39, +48,28,23,195,2,27,248,22,186,7,6,11,11,80,76,84,67,79,76,76,69, 67,84,83,28,192,192,6,0,0,6,0,0,27,28,23,196,1,250,22,186,13, 248,22,144,14,69,97,100,100,111,110,45,100,105,114,247,22,184,7,6,8,8, -99,111,108,108,101,99,116,115,11,27,248,80,159,41,52,36,250,22,84,23,203, +99,111,108,108,101,99,116,115,11,27,248,80,159,42,53,37,250,22,84,23,203, 1,248,22,80,248,22,144,14,72,99,111,108,108,101,99,116,115,45,100,105,114, -23,204,1,28,193,249,22,70,195,194,192,32,50,89,162,8,44,38,8,31,2, +23,204,1,28,193,249,22,70,195,194,192,32,50,89,162,8,44,39,8,31,2, 18,222,33,51,27,249,22,155,14,23,197,2,23,198,2,28,23,193,2,87,94, 23,196,1,27,248,22,95,23,195,2,27,27,248,22,104,23,197,1,27,249,22, 155,14,23,201,2,23,196,2,28,23,193,2,87,94,23,194,1,27,248,22,95, @@ -286,10 +286,10 @@ 103,196,28,28,248,22,79,195,249,22,4,22,168,13,196,11,12,250,22,145,9, 2,13,6,13,13,108,105,115,116,32,111,102,32,112,97,116,104,115,197,250,2, 50,197,195,28,248,22,169,6,197,248,22,180,7,197,196,32,53,89,162,8,44, -38,52,70,102,111,117,110,100,45,101,120,101,99,222,33,56,32,54,89,162,8, -44,39,57,64,110,101,120,116,222,33,55,27,248,22,130,14,23,196,2,28,249, +39,53,70,102,111,117,110,100,45,101,120,101,99,222,33,56,32,54,89,162,8, +44,40,58,64,110,101,120,116,222,33,55,27,248,22,130,14,23,196,2,28,249, 22,177,8,23,195,2,23,197,1,11,28,248,22,190,13,23,194,2,27,249,22, -186,13,23,197,1,23,196,1,28,23,197,2,91,159,38,11,90,161,38,35,11, +186,13,23,197,1,23,196,1,28,23,197,2,91,159,39,11,90,161,39,36,11, 248,22,189,13,23,197,2,87,95,23,195,1,23,194,1,27,28,23,202,2,27, 248,22,130,14,23,199,2,28,249,22,177,8,23,195,2,23,200,2,11,28,248, 22,190,13,23,194,2,250,2,53,23,205,2,23,206,2,249,22,186,13,23,200, @@ -299,8 +299,8 @@ 28,23,193,2,192,87,94,23,193,1,28,23,203,2,11,27,248,22,130,14,23, 200,2,28,249,22,177,8,23,195,2,23,201,1,11,28,248,22,190,13,23,194, 2,250,2,53,23,206,1,23,207,1,249,22,186,13,23,201,1,23,198,1,250, -2,53,205,206,195,192,87,94,23,194,1,28,23,196,2,91,159,38,11,90,161, -38,35,11,248,22,189,13,23,197,2,87,95,23,195,1,23,194,1,27,28,23, +2,53,205,206,195,192,87,94,23,194,1,28,23,196,2,91,159,39,11,90,161, +39,36,11,248,22,189,13,23,197,2,87,95,23,195,1,23,194,1,27,28,23, 201,2,27,248,22,130,14,23,199,2,28,249,22,177,8,23,195,2,23,200,2, 11,28,248,22,190,13,23,194,2,250,2,53,23,204,2,23,205,2,249,22,186, 13,23,200,2,23,198,1,250,2,53,23,204,2,23,205,2,23,196,1,11,28, @@ -309,12 +309,12 @@ 192,11,11,28,23,193,2,192,87,94,23,193,1,28,23,202,2,11,27,248,22, 130,14,23,200,2,28,249,22,177,8,23,195,2,23,201,1,11,28,248,22,190, 13,23,194,2,250,2,53,23,205,1,23,206,1,249,22,186,13,23,201,1,23, -198,1,250,2,53,204,205,195,192,28,23,193,2,91,159,38,11,90,161,38,35, +198,1,250,2,53,204,205,195,192,28,23,193,2,91,159,39,11,90,161,39,36, 11,248,22,189,13,23,199,2,87,95,23,195,1,23,194,1,27,28,23,198,2, 251,2,54,23,198,2,23,203,2,23,201,2,23,202,2,11,28,23,193,2,192, 87,94,23,193,1,27,28,248,22,168,13,195,27,249,22,186,13,197,200,28,28, 248,22,181,13,193,10,248,22,180,13,193,192,11,11,28,192,192,28,198,11,251, -2,54,198,203,201,202,194,32,57,89,162,8,44,39,8,31,2,18,222,33,58, +2,54,198,203,201,202,194,32,57,89,162,8,44,40,8,31,2,18,222,33,58, 28,248,22,78,23,197,2,11,27,248,22,129,14,248,22,71,23,199,2,27,249, 22,186,13,23,196,1,23,197,2,28,248,22,180,13,23,194,2,250,2,53,198, 199,195,87,94,23,193,1,27,248,22,72,23,200,1,28,248,22,78,23,194,2, @@ -339,10 +339,10 @@ 23,196,2,10,248,22,191,13,23,196,2,11,248,22,190,13,23,196,2,11,10, 12,250,22,145,9,2,14,6,29,29,35,102,32,111,114,32,114,101,108,97,116, 105,118,101,32,112,97,116,104,32,111,114,32,115,116,114,105,110,103,23,198,2, -28,28,248,22,190,13,23,195,2,91,159,38,11,90,161,38,35,11,248,22,189, +28,28,248,22,190,13,23,195,2,91,159,39,11,90,161,39,36,11,248,22,189, 13,23,198,2,249,22,175,8,194,68,114,101,108,97,116,105,118,101,11,27,248, -22,186,7,6,4,4,80,65,84,72,27,28,23,194,2,27,249,80,159,40,47, -37,23,197,1,9,28,249,22,175,8,247,22,188,7,2,20,249,22,70,248,22, +22,186,7,6,4,4,80,65,84,72,27,28,23,194,2,27,249,80,159,41,48, +38,23,197,1,9,28,249,22,175,8,247,22,188,7,2,20,249,22,70,248,22, 177,13,5,1,46,194,192,87,94,23,194,1,9,28,248,22,78,23,194,2,11, 27,248,22,129,14,248,22,71,23,196,2,27,249,22,186,13,23,196,1,23,200, 2,28,248,22,180,13,23,194,2,250,2,53,201,202,195,87,94,23,193,1,27, @@ -352,82 +352,82 @@ 248,22,78,23,194,2,11,27,248,22,129,14,248,22,71,195,27,249,22,186,13, 23,196,1,205,28,248,22,180,13,193,250,2,53,23,15,23,16,195,251,2,57, 23,15,23,16,23,17,248,22,72,199,27,248,22,129,14,23,196,1,28,248,22, -180,13,193,250,2,53,198,199,195,11,250,80,159,38,48,36,196,197,11,250,80, -159,38,48,36,196,11,11,87,94,249,22,160,6,247,22,132,5,195,248,22,186, -5,249,22,179,3,35,249,22,163,3,197,198,27,28,23,197,2,87,95,23,196, +180,13,193,250,2,53,198,199,195,11,250,80,159,39,49,37,196,197,11,250,80, +159,39,49,37,196,11,11,87,94,249,22,160,6,247,22,132,5,195,248,22,186, +5,249,22,179,3,36,249,22,163,3,197,198,27,28,23,197,2,87,95,23,196, 1,23,195,1,23,197,1,87,94,23,197,1,27,248,22,144,14,2,19,27,249, -80,159,40,48,36,23,196,1,11,27,27,248,22,182,3,23,200,1,28,192,192, -35,27,27,248,22,182,3,23,202,1,28,192,192,35,249,22,163,5,23,197,1, -83,158,39,20,100,95,89,162,8,44,35,47,9,224,3,2,33,62,23,195,1, -23,196,1,27,248,22,148,5,23,195,1,248,80,159,38,53,36,193,159,35,20, -105,159,35,16,1,11,16,0,83,158,41,20,103,144,67,35,37,117,116,105,108, -115,29,11,11,11,11,11,10,42,80,158,35,35,20,105,159,37,16,17,2,1, +80,159,41,49,37,23,196,1,11,27,27,248,22,182,3,23,200,1,28,192,192, +36,27,27,248,22,182,3,23,202,1,28,192,192,36,249,22,163,5,23,197,1, +83,158,40,20,100,95,89,162,8,44,36,48,9,224,3,2,33,62,23,195,1, +23,196,1,27,248,22,148,5,23,195,1,248,80,159,39,54,37,193,159,36,20, +105,159,36,16,1,11,16,0,83,158,42,20,103,144,67,35,37,117,116,105,108, +115,29,11,11,11,11,11,10,43,80,158,36,36,20,105,159,38,16,17,2,1, 2,2,2,3,2,4,2,5,2,6,2,7,2,8,2,9,2,10,2,11,2, 12,2,13,2,14,2,15,30,2,17,1,20,112,97,114,97,109,101,116,101,114, 105,122,97,116,105,111,110,45,107,101,121,4,30,2,17,1,23,101,120,116,101, 110,100,45,112,97,114,97,109,101,116,101,114,105,122,97,116,105,111,110,3,16, -0,16,0,35,16,0,35,16,4,2,5,2,4,2,2,2,8,39,11,11,38, -35,11,11,11,16,11,2,7,2,6,2,15,2,14,2,12,2,11,2,3,2, +0,16,0,36,16,0,36,16,4,2,5,2,4,2,2,2,8,40,11,11,39, +36,11,11,11,16,11,2,7,2,6,2,15,2,14,2,12,2,11,2,3,2, 10,2,13,2,9,2,1,16,11,11,11,11,11,11,11,11,11,11,11,11,16, 11,2,7,2,6,2,15,2,14,2,12,2,11,2,3,2,10,2,13,2,9, -2,1,46,46,36,11,11,11,16,0,16,0,16,0,35,35,11,11,11,11,16, -0,16,0,16,0,35,35,16,0,16,17,83,158,35,16,2,89,162,8,44,36, -50,2,18,223,0,33,29,80,159,35,53,36,83,158,35,16,2,89,162,8,44, -36,55,2,18,223,0,33,30,80,159,35,52,36,83,158,35,16,2,32,0,89, -162,43,36,44,2,1,222,33,31,80,159,35,35,36,83,158,35,16,2,249,22, -171,6,7,92,7,92,80,159,35,36,36,83,158,35,16,2,89,162,43,36,53, -2,3,223,0,33,32,80,159,35,37,36,83,158,35,16,2,32,0,89,162,8, -44,37,49,2,4,222,33,33,80,159,35,38,36,83,158,35,16,2,32,0,89, -162,8,44,38,50,2,5,222,33,35,80,159,35,39,36,83,158,35,16,2,32, -0,89,162,8,45,37,49,2,6,222,33,39,80,159,35,40,36,83,158,35,16, -2,32,0,89,162,43,39,51,2,7,222,33,42,80,159,35,41,36,83,158,35, -16,2,32,0,89,162,43,38,49,2,8,222,33,43,80,159,35,42,36,83,158, -35,16,2,32,0,89,162,43,37,52,2,9,222,33,44,80,159,35,43,36,83, -158,35,16,2,32,0,89,162,43,37,53,2,10,222,33,45,80,159,35,44,36, -83,158,35,16,2,32,0,89,162,43,36,43,2,11,222,33,46,80,159,35,45, -36,83,158,35,16,2,83,158,38,20,99,96,2,12,89,162,43,35,43,9,223, -0,33,47,89,162,43,36,44,9,223,0,33,48,89,162,43,37,54,9,223,0, -33,49,80,159,35,46,36,83,158,35,16,2,27,248,22,151,14,248,22,180,7, +2,1,47,47,37,11,11,11,16,0,16,0,16,0,36,36,11,11,11,11,16, +0,16,0,16,0,36,36,16,0,16,17,83,158,36,16,2,89,162,8,44,37, +51,2,18,223,0,33,29,80,159,36,54,37,83,158,36,16,2,89,162,8,44, +37,56,2,18,223,0,33,30,80,159,36,53,37,83,158,36,16,2,32,0,89, +162,44,37,45,2,1,222,33,31,80,159,36,36,37,83,158,36,16,2,249,22, +171,6,7,92,7,92,80,159,36,37,37,83,158,36,16,2,89,162,44,37,54, +2,3,223,0,33,32,80,159,36,38,37,83,158,36,16,2,32,0,89,162,8, +44,38,50,2,4,222,33,33,80,159,36,39,37,83,158,36,16,2,32,0,89, +162,8,44,39,51,2,5,222,33,35,80,159,36,40,37,83,158,36,16,2,32, +0,89,162,8,45,38,50,2,6,222,33,39,80,159,36,41,37,83,158,36,16, +2,32,0,89,162,44,40,52,2,7,222,33,42,80,159,36,42,37,83,158,36, +16,2,32,0,89,162,44,39,50,2,8,222,33,43,80,159,36,43,37,83,158, +36,16,2,32,0,89,162,44,38,53,2,9,222,33,44,80,159,36,44,37,83, +158,36,16,2,32,0,89,162,44,38,54,2,10,222,33,45,80,159,36,45,37, +83,158,36,16,2,32,0,89,162,44,37,44,2,11,222,33,46,80,159,36,46, +37,83,158,36,16,2,83,158,39,20,99,96,2,12,89,162,44,36,44,9,223, +0,33,47,89,162,44,37,45,9,223,0,33,48,89,162,44,38,55,9,223,0, +33,49,80,159,36,47,37,83,158,36,16,2,27,248,22,151,14,248,22,180,7, 27,28,249,22,175,8,247,22,188,7,2,20,6,1,1,59,6,1,1,58,250, 22,153,7,6,14,14,40,91,94,126,97,93,42,41,126,97,40,46,42,41,23, -196,2,23,196,1,89,162,8,44,37,47,2,13,223,0,33,52,80,159,35,47, -36,83,158,35,16,2,83,158,38,20,99,96,2,14,89,162,8,44,38,59,9, -223,0,33,59,89,162,43,37,46,9,223,0,33,60,89,162,43,36,45,9,223, -0,33,61,80,159,35,48,36,83,158,35,16,2,89,162,8,44,38,51,2,15, -223,0,33,63,80,159,35,49,36,94,29,94,2,16,68,35,37,107,101,114,110, -101,108,11,29,94,2,16,69,35,37,109,105,110,45,115,116,120,11,9,9,9, -35,0}; - EVAL_ONE_SIZED_STR((char *)expr, 6238); +196,2,23,196,1,89,162,8,44,38,48,2,13,223,0,33,52,80,159,36,48, +37,83,158,36,16,2,83,158,39,20,99,96,2,14,89,162,8,44,39,8,24, +9,223,0,33,59,89,162,44,38,47,9,223,0,33,60,89,162,44,37,46,9, +223,0,33,61,80,159,36,49,37,83,158,36,16,2,89,162,8,44,39,52,2, +15,223,0,33,63,80,159,36,50,37,94,29,94,2,16,68,35,37,107,101,114, +110,101,108,11,29,94,2,16,69,35,37,109,105,110,45,115,116,120,11,9,9, +9,36,0}; + EVAL_ONE_SIZED_STR((char *)expr, 6239); } { - SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,53,8,0,0,0,1,0,0,6,0,19,0, + SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,54,8,0,0,0,1,0,0,6,0,19,0, 34,0,48,0,62,0,76,0,118,0,0,0,53,1,0,0,65,113,117,111,116, 101,29,94,2,1,67,35,37,117,116,105,108,115,11,29,94,2,1,69,35,37, 110,101,116,119,111,114,107,11,29,94,2,1,68,35,37,112,97,114,97,109,122, 11,29,94,2,1,68,35,37,101,120,112,111,98,115,11,29,94,2,1,68,35, -37,107,101,114,110,101,108,11,97,35,11,8,240,169,76,0,0,98,159,2,2, -35,35,159,2,3,35,35,159,2,4,35,35,159,2,5,35,35,159,2,6,35, -35,159,2,6,35,35,16,0,159,35,20,105,159,35,16,1,11,16,0,83,158, -41,20,103,144,69,35,37,98,117,105,108,116,105,110,29,11,11,11,11,11,18, -96,11,42,42,42,35,80,158,35,35,20,105,159,35,16,0,16,0,16,0,35, -16,0,35,16,0,35,11,11,38,35,11,11,11,16,0,16,0,16,0,35,35, -36,11,11,11,16,0,16,0,16,0,35,35,11,11,11,11,16,0,16,0,16, -0,35,35,16,0,16,0,102,2,6,2,5,29,94,2,1,69,35,37,102,111, +37,107,101,114,110,101,108,11,97,36,11,8,240,178,76,0,0,98,159,2,2, +36,36,159,2,3,36,36,159,2,4,36,36,159,2,5,36,36,159,2,6,36, +36,159,2,6,36,36,16,0,159,36,20,105,159,36,16,1,11,16,0,83,158, +42,20,103,144,69,35,37,98,117,105,108,116,105,110,29,11,11,11,11,11,18, +96,11,43,43,43,36,80,158,36,36,20,105,159,36,16,0,16,0,16,0,36, +16,0,36,16,0,36,11,11,39,36,11,11,11,16,0,16,0,16,0,36,36, +37,11,11,11,16,0,16,0,16,0,36,36,11,11,11,11,16,0,16,0,16, +0,36,36,16,0,16,0,102,2,6,2,5,29,94,2,1,69,35,37,102,111, 114,101,105,103,110,11,29,94,2,1,68,35,37,117,110,115,97,102,101,11,29, 94,2,1,69,35,37,102,108,102,120,110,117,109,11,2,4,2,3,2,2,29, 94,2,1,67,35,37,112,108,97,99,101,11,29,94,2,1,69,35,37,102,117, -116,117,114,101,115,11,9,9,9,35,0}; +116,117,114,101,115,11,9,9,9,36,0}; EVAL_ONE_SIZED_STR((char *)expr, 346); } { - SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,53,65,0,0,0,1,0,0,11,0,38,0, + SHARED_OK static MZCOMPILED_STRING_FAR unsigned char expr[] = {35,126,7,52,46,50,46,53,46,54,65,0,0,0,1,0,0,11,0,38,0, 44,0,57,0,66,0,73,0,95,0,117,0,143,0,155,0,173,0,193,0,205, 0,221,0,244,0,0,1,31,1,38,1,43,1,48,1,53,1,58,1,67,1, 72,1,76,1,84,1,93,1,114,1,144,1,175,1,232,1,24,2,64,4,83, 4,96,4,254,4,10,5,144,5,186,6,53,7,59,7,73,7,85,7,175,7, 188,7,51,8,63,8,153,8,166,8,29,9,56,9,68,9,158,9,171,9,34, 10,47,10,166,10,174,10,3,11,5,11,74,11,69,18,121,18,144,18,0,0, -48,21,0,0,70,100,108,108,45,115,117,102,102,105,120,1,25,100,101,102,97, +49,21,0,0,70,100,108,108,45,115,117,102,102,105,120,1,25,100,101,102,97, 117,108,116,45,108,111,97,100,47,117,115,101,45,99,111,109,112,105,108,101,100, 65,113,117,111,116,101,29,94,2,3,67,35,37,117,116,105,108,115,11,68,35, 37,112,97,114,97,109,122,29,94,2,3,2,5,11,1,20,112,97,114,97,109, @@ -443,44 +443,44 @@ 100,117,108,101,45,110,97,109,101,45,114,101,115,111,108,118,101,114,29,94,2, 3,2,5,11,64,98,111,111,116,64,115,101,97,108,64,115,97,109,101,5,3, 46,122,111,6,6,6,110,97,116,105,118,101,64,108,111,111,112,63,108,105,98, -67,105,103,110,111,114,101,100,249,22,14,195,80,159,37,45,37,250,22,186,13, -23,197,1,23,199,1,249,80,159,42,38,37,23,198,1,2,22,252,22,186,13, -23,199,1,23,201,1,2,23,247,22,189,7,249,80,159,44,38,37,23,200,1, -80,159,44,35,37,87,94,23,194,1,27,250,22,139,14,196,11,32,0,89,162, -8,44,35,40,9,222,11,28,192,249,22,70,195,194,11,27,252,22,186,13,23, -200,1,23,202,1,2,23,247,22,189,7,249,80,159,45,38,37,23,201,1,80, -159,45,35,37,27,250,22,139,14,196,11,32,0,89,162,8,44,35,40,9,222, +67,105,103,110,111,114,101,100,249,22,14,195,80,159,38,46,38,250,22,186,13, +23,197,1,23,199,1,249,80,159,43,39,38,23,198,1,2,22,252,22,186,13, +23,199,1,23,201,1,2,23,247,22,189,7,249,80,159,45,39,38,23,200,1, +80,159,45,36,38,87,94,23,194,1,27,250,22,139,14,196,11,32,0,89,162, +8,44,36,41,9,222,11,28,192,249,22,70,195,194,11,27,252,22,186,13,23, +200,1,23,202,1,2,23,247,22,189,7,249,80,159,46,39,38,23,201,1,80, +159,46,36,38,27,250,22,139,14,196,11,32,0,89,162,8,44,36,41,9,222, 11,28,192,249,22,70,195,194,11,27,250,22,186,13,23,198,1,23,200,1,249, -80,159,43,38,37,23,199,1,2,22,27,250,22,139,14,196,11,32,0,89,162, -8,44,35,40,9,222,11,28,192,249,22,70,195,194,11,87,94,28,248,80,159, -36,37,37,23,195,2,12,250,22,145,9,77,108,111,97,100,47,117,115,101,45, +80,159,44,39,38,23,199,1,2,22,27,250,22,139,14,196,11,32,0,89,162, +8,44,36,41,9,222,11,28,192,249,22,70,195,194,11,87,94,28,248,80,159, +37,38,38,23,195,2,12,250,22,145,9,77,108,111,97,100,47,117,115,101,45, 99,111,109,112,105,108,101,100,6,25,25,112,97,116,104,32,111,114,32,118,97, -108,105,100,45,112,97,116,104,32,115,116,114,105,110,103,23,197,2,91,159,41, -11,90,161,36,35,11,28,248,22,128,14,23,201,2,23,200,1,27,247,22,137, -5,28,23,193,2,249,22,129,14,23,203,1,23,195,1,200,90,161,38,36,11, -248,22,189,13,23,194,2,87,94,23,196,1,90,161,36,39,11,28,249,22,175, +108,105,100,45,112,97,116,104,32,115,116,114,105,110,103,23,197,2,91,159,42, +11,90,161,37,36,11,28,248,22,128,14,23,201,2,23,200,1,27,247,22,137, +5,28,23,193,2,249,22,129,14,23,203,1,23,195,1,200,90,161,39,37,11, +248,22,189,13,23,194,2,87,94,23,196,1,90,161,37,40,11,28,249,22,175, 8,23,196,2,68,114,101,108,97,116,105,118,101,87,94,23,194,1,2,21,23, -194,1,90,161,36,40,11,247,22,147,14,27,89,162,43,36,49,62,122,111,225, -7,5,3,33,28,27,89,162,43,36,51,9,225,8,6,4,33,29,27,249,22, -5,89,162,8,44,36,46,9,223,5,33,30,23,203,2,27,28,23,195,1,27, -249,22,5,89,162,8,44,36,52,9,225,13,11,9,33,31,23,205,2,27,28, +194,1,90,161,37,41,11,247,22,147,14,27,89,162,44,37,50,62,122,111,225, +7,5,3,33,28,27,89,162,44,37,52,9,225,8,6,4,33,29,27,249,22, +5,89,162,8,44,37,47,9,223,5,33,30,23,203,2,27,28,23,195,1,27, +249,22,5,89,162,8,44,37,53,9,225,13,11,9,33,31,23,205,2,27,28, 23,196,2,11,193,28,192,192,28,193,28,23,196,2,28,249,22,175,3,248,22, 72,196,248,22,72,23,199,2,193,11,11,11,11,28,23,193,2,87,98,23,202, -1,23,199,1,23,197,1,23,196,1,23,194,1,20,14,159,80,159,45,39,37, -250,80,159,48,40,37,249,22,27,11,80,159,50,39,37,22,137,5,28,248,22, +1,23,199,1,23,197,1,23,196,1,23,194,1,20,14,159,80,159,46,40,38, +250,80,159,49,41,38,249,22,27,11,80,159,51,40,38,22,137,5,28,248,22, 168,13,23,205,2,23,204,1,87,94,23,204,1,247,22,145,14,249,247,22,150, 14,248,22,71,195,206,87,94,23,193,1,27,28,23,197,1,27,249,22,5,83, -158,39,20,100,94,89,162,8,44,36,50,9,225,14,12,10,33,32,23,203,1, +158,40,20,100,94,89,162,8,44,37,51,9,225,14,12,10,33,32,23,203,1, 23,206,1,27,28,23,197,2,11,193,28,192,192,28,193,28,196,28,249,22,175, 3,248,22,72,196,248,22,72,199,193,11,11,11,87,95,23,203,1,23,200,1, -11,28,23,193,2,87,94,23,198,1,20,14,159,80,159,46,39,37,250,80,159, -49,40,37,249,22,27,11,80,159,51,39,37,22,137,5,28,248,22,168,13,23, +11,28,23,193,2,87,94,23,198,1,20,14,159,80,159,47,40,38,250,80,159, +50,41,38,249,22,27,11,80,159,52,40,38,22,137,5,28,248,22,168,13,23, 206,2,23,205,1,87,94,23,205,1,247,22,145,14,249,247,22,135,5,248,22, -71,195,23,15,87,94,23,193,1,20,14,159,80,159,46,39,37,250,80,159,49, -40,37,249,22,27,11,80,159,51,39,37,22,137,5,28,248,22,168,13,23,206, +71,195,23,15,87,94,23,193,1,20,14,159,80,159,47,40,38,250,80,159,50, +41,38,249,22,27,11,80,159,52,40,38,22,137,5,28,248,22,168,13,23,206, 2,23,205,1,87,94,23,205,1,247,22,145,14,249,247,22,135,5,199,23,15, 0,17,35,114,120,34,94,40,46,42,63,41,47,40,46,42,41,36,34,32,35, -89,162,8,44,36,58,2,24,222,33,36,27,249,22,155,14,2,34,23,196,2, +89,162,8,44,37,59,2,24,222,33,36,27,249,22,155,14,2,34,23,196,2, 28,23,193,2,87,94,23,194,1,249,22,70,248,22,95,23,196,2,27,248,22, 104,23,197,1,27,249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23, 194,1,249,22,70,248,22,95,23,196,2,27,248,22,104,23,197,1,27,249,22, @@ -488,11 +488,11 @@ 95,23,196,2,27,248,22,104,23,197,1,27,249,22,155,14,2,34,23,196,2, 28,23,193,2,87,94,23,194,1,249,22,70,248,22,95,23,196,2,248,2,35, 248,22,104,23,197,1,248,22,80,194,248,22,80,194,248,22,80,194,248,22,80, -194,32,37,89,162,43,36,54,2,24,222,33,38,28,248,22,78,248,22,72,23, -195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37,35,11,27,248, +194,32,37,89,162,44,37,55,2,24,222,33,38,28,248,22,78,248,22,72,23, +195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38,36,11,27,248, 22,72,196,28,248,22,78,248,22,72,23,195,2,249,22,7,9,248,22,71,195, -91,159,37,11,90,161,37,35,11,27,248,22,72,196,28,248,22,78,248,22,72, -23,195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37,35,11,248, +91,159,38,11,90,161,38,36,11,27,248,22,72,196,28,248,22,78,248,22,72, +23,195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38,36,11,248, 2,37,248,22,72,196,249,22,7,249,22,70,248,22,71,199,196,195,249,22,7, 249,22,70,248,22,71,199,196,195,249,22,7,249,22,70,248,22,71,199,196,195, 27,27,249,22,155,14,2,34,23,197,2,28,23,193,2,87,94,23,195,1,249, @@ -503,55 +503,55 @@ 1,27,249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23,194,1,249, 22,70,248,22,95,23,196,2,248,2,35,248,22,104,23,197,1,248,22,80,194, 248,22,80,194,248,22,80,194,248,22,80,195,28,23,195,1,192,28,248,22,78, -248,22,72,23,195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37, -35,11,27,248,22,72,196,28,248,22,78,248,22,72,23,195,2,249,22,7,9, -248,22,71,195,91,159,37,11,90,161,37,35,11,27,248,22,72,196,28,248,22, -78,248,22,72,23,195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161, -37,35,11,248,2,37,248,22,72,196,249,22,7,249,22,70,248,22,71,199,196, +248,22,72,23,195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38, +36,11,27,248,22,72,196,28,248,22,78,248,22,72,23,195,2,249,22,7,9, +248,22,71,195,91,159,38,11,90,161,38,36,11,27,248,22,72,196,28,248,22, +78,248,22,72,23,195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161, +38,36,11,248,2,37,248,22,72,196,249,22,7,249,22,70,248,22,71,199,196, 195,249,22,7,249,22,70,248,22,71,199,196,195,249,22,7,249,22,70,248,22, 71,199,196,195,87,95,28,248,22,179,4,195,12,250,22,145,9,2,17,6,20, 20,114,101,115,111,108,118,101,100,45,109,111,100,117,108,101,45,112,97,116,104, 197,28,24,193,2,248,24,194,1,195,87,94,23,193,1,12,27,27,250,22,145, -2,80,159,41,42,37,248,22,175,14,247,22,148,12,11,28,23,193,2,192,87, -94,23,193,1,27,247,22,129,2,87,94,250,22,143,2,80,159,42,42,37,248, +2,80,159,42,43,38,248,22,175,14,247,22,148,12,11,28,23,193,2,192,87, +94,23,193,1,27,247,22,129,2,87,94,250,22,143,2,80,159,43,43,38,248, 22,175,14,247,22,148,12,195,192,250,22,143,2,195,198,66,97,116,116,97,99, 104,251,211,197,198,199,10,28,192,250,22,144,9,11,196,195,248,22,142,9,194, -32,43,89,162,43,36,51,2,24,222,33,44,28,248,22,78,248,22,72,23,195, -2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37,35,11,27,248,22, +32,43,89,162,44,37,52,2,24,222,33,44,28,248,22,78,248,22,72,23,195, +2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38,36,11,27,248,22, 72,196,28,248,22,78,248,22,72,23,195,2,249,22,7,9,248,22,71,195,91, -159,37,11,90,161,37,35,11,248,2,43,248,22,72,196,249,22,7,249,22,70, +159,38,11,90,161,38,36,11,248,2,43,248,22,72,196,249,22,7,249,22,70, 248,22,71,199,196,195,249,22,7,249,22,70,248,22,71,199,196,195,32,45,89, -162,8,44,36,54,2,24,222,33,46,27,249,22,155,14,2,34,23,196,2,28, +162,8,44,37,55,2,24,222,33,46,27,249,22,155,14,2,34,23,196,2,28, 23,193,2,87,94,23,194,1,249,22,70,248,22,95,23,196,2,27,248,22,104, 23,197,1,27,249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23,194, 1,249,22,70,248,22,95,23,196,2,27,248,22,104,23,197,1,27,249,22,155, 14,2,34,23,196,2,28,23,193,2,87,94,23,194,1,249,22,70,248,22,95, 23,196,2,248,2,45,248,22,104,23,197,1,248,22,80,194,248,22,80,194,248, -22,80,194,32,47,89,162,43,36,51,2,24,222,33,48,28,248,22,78,248,22, -72,23,195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37,35,11, +22,80,194,32,47,89,162,44,37,52,2,24,222,33,48,28,248,22,78,248,22, +72,23,195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38,36,11, 27,248,22,72,196,28,248,22,78,248,22,72,23,195,2,249,22,7,9,248,22, -71,195,91,159,37,11,90,161,37,35,11,248,2,47,248,22,72,196,249,22,7, +71,195,91,159,38,11,90,161,38,36,11,248,2,47,248,22,72,196,249,22,7, 249,22,70,248,22,71,199,196,195,249,22,7,249,22,70,248,22,71,199,196,195, -32,49,89,162,8,44,36,54,2,24,222,33,50,27,249,22,155,14,2,34,23, +32,49,89,162,8,44,37,55,2,24,222,33,50,27,249,22,155,14,2,34,23, 196,2,28,23,193,2,87,94,23,194,1,249,22,70,248,22,95,23,196,2,27, 248,22,104,23,197,1,27,249,22,155,14,2,34,23,196,2,28,23,193,2,87, 94,23,194,1,249,22,70,248,22,95,23,196,2,27,248,22,104,23,197,1,27, 249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23,194,1,249,22,70, 248,22,95,23,196,2,248,2,49,248,22,104,23,197,1,248,22,80,194,248,22, 80,194,248,22,80,194,28,249,22,175,6,194,6,1,1,46,2,21,28,249,22, -175,6,194,6,2,2,46,46,62,117,112,192,32,52,89,162,43,36,51,2,24, +175,6,194,6,2,2,46,46,62,117,112,192,32,52,89,162,44,37,52,2,24, 222,33,53,28,248,22,78,248,22,72,23,195,2,249,22,7,9,248,22,71,195, -91,159,37,11,90,161,37,35,11,27,248,22,72,196,28,248,22,78,248,22,72, -23,195,2,249,22,7,9,248,22,71,195,91,159,37,11,90,161,37,35,11,248, +91,159,38,11,90,161,38,36,11,27,248,22,72,196,28,248,22,78,248,22,72, +23,195,2,249,22,7,9,248,22,71,195,91,159,38,11,90,161,38,36,11,248, 2,52,248,22,72,196,249,22,7,249,22,70,248,22,71,199,196,195,249,22,7, -249,22,70,248,22,71,199,196,195,32,54,89,162,8,44,36,54,2,24,222,33, +249,22,70,248,22,71,199,196,195,32,54,89,162,8,44,37,55,2,24,222,33, 55,27,249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23,194,1,249, 22,70,248,22,95,23,196,2,27,248,22,104,23,197,1,27,249,22,155,14,2, 34,23,196,2,28,23,193,2,87,94,23,194,1,249,22,70,248,22,95,23,196, 2,27,248,22,104,23,197,1,27,249,22,155,14,2,34,23,196,2,28,23,193, 2,87,94,23,194,1,249,22,70,248,22,95,23,196,2,248,2,54,248,22,104, 23,197,1,248,22,80,194,248,22,80,194,248,22,80,194,32,56,89,162,8,44, -36,54,2,24,222,33,57,27,249,22,155,14,2,34,23,196,2,28,23,193,2, +37,55,2,24,222,33,57,27,249,22,155,14,2,34,23,196,2,28,23,193,2, 87,94,23,194,1,249,22,70,248,22,95,23,196,2,27,248,22,104,23,197,1, 27,249,22,155,14,2,34,23,196,2,28,23,193,2,87,94,23,194,1,249,22, 70,248,22,95,23,196,2,27,248,22,104,23,197,1,27,249,22,155,14,2,34, @@ -561,9 +561,9 @@ 1,28,249,22,175,8,248,22,71,23,200,2,23,196,1,251,22,142,9,2,17, 6,26,26,99,121,99,108,101,32,105,110,32,108,111,97,100,105,110,103,32,97, 116,32,126,101,58,32,126,101,23,200,1,249,22,2,22,72,248,22,85,249,22, -70,23,206,1,23,202,1,12,12,247,192,20,14,159,80,159,39,44,37,249,22, -70,248,22,175,14,247,22,148,12,23,197,1,20,14,159,80,159,39,39,37,250, -80,159,42,40,37,249,22,27,11,80,159,44,39,37,22,161,4,23,196,1,249, +70,23,206,1,23,202,1,12,12,247,192,20,14,159,80,159,40,45,38,249,22, +70,248,22,175,14,247,22,148,12,23,197,1,20,14,159,80,159,40,40,38,250, +80,159,43,41,38,249,22,27,11,80,159,45,40,38,22,161,4,23,196,1,249, 247,22,136,5,23,198,1,248,22,58,248,22,172,13,23,198,1,87,94,28,28, 248,22,168,13,23,196,2,10,248,22,187,4,23,196,2,12,28,23,197,2,250, 22,144,9,11,6,15,15,98,97,100,32,109,111,100,117,108,101,32,112,97,116, @@ -571,51 +571,51 @@ 97,116,104,32,111,114,32,112,97,116,104,23,198,2,28,28,248,22,68,23,196, 2,249,22,175,8,248,22,71,23,198,2,2,3,11,248,22,180,4,248,22,95, 196,28,28,248,22,68,23,196,2,249,22,175,8,248,22,71,23,198,2,66,112, -108,97,110,101,116,11,87,94,28,207,12,20,14,159,80,159,36,51,37,80,158, -36,49,90,161,36,35,10,249,22,162,4,21,94,2,25,6,18,18,112,108,97, +108,97,110,101,116,11,87,94,28,207,12,20,14,159,80,159,37,52,38,80,158, +37,50,90,161,37,36,10,249,22,162,4,21,94,2,25,6,18,18,112,108,97, 110,101,116,47,114,101,115,111,108,118,101,114,46,115,115,1,27,112,108,97,110, 101,116,45,109,111,100,117,108,101,45,110,97,109,101,45,114,101,115,111,108,118, -101,114,12,252,212,199,200,201,202,80,158,41,49,87,94,23,193,1,27,89,162, -8,44,36,45,79,115,104,111,119,45,99,111,108,108,101,99,116,105,111,110,45, +101,114,12,252,212,199,200,201,202,80,158,42,50,87,94,23,193,1,27,89,162, +8,44,37,46,79,115,104,111,119,45,99,111,108,108,101,99,116,105,111,110,45, 101,114,114,223,5,33,42,27,28,248,22,55,23,198,2,27,250,22,145,2,80, -159,42,43,37,249,22,70,23,203,2,247,22,146,14,11,28,23,193,2,192,87, -94,23,193,1,91,159,37,11,90,161,37,35,11,27,248,22,61,23,202,2,248, -2,43,248,2,45,23,195,1,27,251,80,159,46,52,37,2,17,23,202,1,28, +159,43,44,38,249,22,70,23,203,2,247,22,146,14,11,28,23,193,2,192,87, +94,23,193,1,91,159,38,11,90,161,38,36,11,27,248,22,61,23,202,2,248, +2,43,248,2,45,23,195,1,27,251,80,159,47,53,38,2,17,23,202,1,28, 248,22,78,23,199,2,23,199,2,248,22,71,23,199,2,28,248,22,78,23,199, 2,9,248,22,72,23,199,2,249,22,186,13,23,195,1,28,248,22,78,23,197, 1,87,94,23,197,1,6,7,7,109,97,105,110,46,115,115,249,22,128,7,23, 199,1,6,3,3,46,115,115,28,248,22,169,6,23,198,2,87,94,23,194,1, -27,27,28,23,200,2,28,249,22,175,8,23,202,2,80,158,42,46,80,158,40, -47,27,248,22,181,4,23,202,2,28,248,22,168,13,23,194,2,91,159,38,11, -90,161,38,35,11,248,22,189,13,23,197,1,87,95,83,160,37,11,80,158,44, -46,23,204,2,83,160,37,11,80,158,44,47,192,192,11,11,28,23,193,2,192, +27,27,28,23,200,2,28,249,22,175,8,23,202,2,80,158,43,47,80,158,41, +48,27,248,22,181,4,23,202,2,28,248,22,168,13,23,194,2,91,159,39,11, +90,161,39,36,11,248,22,189,13,23,197,1,87,95,83,160,38,11,80,158,45, +47,23,204,2,83,160,38,11,80,158,45,48,192,192,11,11,28,23,193,2,192, 87,94,23,193,1,27,247,22,137,5,28,23,193,2,192,87,94,23,193,1,247, -22,145,14,27,250,22,145,2,80,159,43,43,37,249,22,70,23,204,2,23,199, -2,11,28,23,193,2,192,87,94,23,193,1,91,159,37,11,90,161,37,35,11, +22,145,14,27,250,22,145,2,80,159,44,44,38,249,22,70,23,204,2,23,199, +2,11,28,23,193,2,192,87,94,23,193,1,91,159,38,11,90,161,38,36,11, 248,2,47,248,2,49,23,203,2,250,22,1,22,186,13,23,199,1,249,22,84, -249,22,2,32,0,89,162,8,44,36,43,9,222,33,51,23,200,1,248,22,80, +249,22,2,32,0,89,162,8,44,37,44,9,222,33,51,23,200,1,248,22,80, 23,200,1,28,248,22,168,13,23,198,2,87,94,23,194,1,28,248,22,191,13, 23,198,2,23,197,2,248,22,80,6,26,26,32,40,97,32,112,97,116,104,32, 109,117,115,116,32,98,101,32,97,98,115,111,108,117,116,101,41,28,249,22,175, -8,248,22,71,23,200,2,2,25,27,250,22,145,2,80,159,42,43,37,249,22, +8,248,22,71,23,200,2,2,25,27,250,22,145,2,80,159,43,44,38,249,22, 70,23,203,2,247,22,146,14,11,28,23,193,2,192,87,94,23,193,1,91,159, -38,11,90,161,37,35,11,27,248,22,95,23,203,2,248,2,52,248,2,54,23, -195,1,90,161,36,37,11,28,248,22,78,248,22,97,23,203,2,28,248,22,78, +39,11,90,161,38,36,11,27,248,22,95,23,203,2,248,2,52,248,2,54,23, +195,1,90,161,37,38,11,28,248,22,78,248,22,97,23,203,2,28,248,22,78, 23,194,2,249,22,157,14,0,8,35,114,120,34,91,46,93,34,23,196,2,11, 10,27,27,28,23,197,2,249,22,84,28,248,22,78,248,22,97,23,207,2,21, 93,6,5,5,109,122,108,105,98,249,22,1,22,84,249,22,2,32,0,89,162, -8,44,36,43,9,222,33,58,248,22,97,23,210,2,23,197,2,28,248,22,78, -23,196,2,248,22,80,23,197,2,23,195,2,251,80,159,48,52,37,2,17,23, +8,44,37,44,9,222,33,58,248,22,97,23,210,2,23,197,2,28,248,22,78, +23,196,2,248,22,80,23,197,2,23,195,2,251,80,159,49,53,38,2,17,23, 204,1,248,22,71,23,198,2,248,22,72,23,198,1,249,22,186,13,23,195,1, 28,23,198,1,87,94,23,196,1,23,197,1,28,248,22,78,23,197,1,87,94, 23,197,1,6,7,7,109,97,105,110,46,115,115,28,249,22,157,14,0,8,35, 114,120,34,91,46,93,34,23,199,2,23,197,1,249,22,128,7,23,199,1,6, 3,3,46,115,115,28,249,22,175,8,248,22,71,23,200,2,64,102,105,108,101, 249,22,129,14,248,22,133,14,248,22,95,23,201,2,27,28,23,201,2,28,249, -22,175,8,23,203,2,80,158,43,46,80,158,41,47,27,248,22,181,4,23,203, -2,28,248,22,168,13,23,194,2,91,159,38,11,90,161,38,35,11,248,22,189, -13,23,197,1,87,95,83,160,37,11,80,158,45,46,23,205,2,83,160,37,11, -80,158,45,47,192,192,11,11,28,23,193,2,192,87,94,23,193,1,27,247,22, +22,175,8,23,203,2,80,158,44,47,80,158,42,48,27,248,22,181,4,23,203, +2,28,248,22,168,13,23,194,2,91,159,39,11,90,161,39,36,11,248,22,189, +13,23,197,1,87,95,83,160,38,11,80,158,46,47,23,205,2,83,160,38,11, +80,158,46,48,192,192,11,11,28,23,193,2,192,87,94,23,193,1,27,247,22, 137,5,28,23,193,2,192,87,94,23,193,1,247,22,145,14,12,87,94,28,28, 248,22,168,13,23,194,2,10,248,22,191,7,23,194,2,87,94,23,199,1,12, 28,23,199,2,250,22,144,9,67,114,101,113,117,105,114,101,249,22,153,7,6, @@ -623,39 +623,39 @@ 198,2,248,22,71,23,199,2,6,0,0,23,202,1,87,94,23,199,1,250,22, 145,9,2,17,249,22,153,7,6,13,13,109,111,100,117,108,101,32,112,97,116, 104,126,97,28,23,198,2,248,22,71,23,199,2,6,0,0,23,200,2,27,28, -248,22,191,7,23,195,2,249,22,132,8,23,196,2,35,249,22,131,14,248,22, +248,22,191,7,23,195,2,249,22,132,8,23,196,2,36,249,22,131,14,248,22, 132,14,23,197,2,11,27,28,248,22,191,7,23,196,2,249,22,132,8,23,197, -2,36,248,80,159,41,53,37,23,195,2,91,159,38,11,90,161,38,35,11,28, -248,22,191,7,23,199,2,250,22,7,2,26,249,22,132,8,23,203,2,37,2, +2,37,248,80,159,42,54,38,23,195,2,91,159,39,11,90,161,39,36,11,28, +248,22,191,7,23,199,2,250,22,7,2,26,249,22,132,8,23,203,2,38,2, 26,248,22,189,13,23,198,2,87,95,23,195,1,23,193,1,27,28,248,22,191, -7,23,200,2,249,22,132,8,23,201,2,38,249,80,159,46,54,37,23,197,2, -5,0,27,28,248,22,191,7,23,201,2,249,22,132,8,23,202,2,39,248,22, -180,4,23,200,2,27,27,250,22,145,2,80,159,50,42,37,248,22,175,14,247, +7,23,200,2,249,22,132,8,23,201,2,39,249,80,159,47,55,38,23,197,2, +5,0,27,28,248,22,191,7,23,201,2,249,22,132,8,23,202,2,40,248,22, +180,4,23,200,2,27,27,250,22,145,2,80,159,51,43,38,248,22,175,14,247, 22,148,12,11,28,23,193,2,192,87,94,23,193,1,27,247,22,129,2,87,94, -250,22,143,2,80,159,51,42,37,248,22,175,14,247,22,148,12,195,192,87,95, +250,22,143,2,80,159,52,43,38,248,22,175,14,247,22,148,12,195,192,87,95, 28,23,208,1,27,250,22,145,2,23,197,2,197,11,28,23,193,1,12,87,95, -27,27,28,248,22,17,80,159,50,45,37,80,159,49,45,37,247,22,19,250,22, -25,248,22,23,23,197,2,80,159,52,44,37,23,196,1,27,248,22,175,14,247, -22,148,12,249,22,3,83,158,39,20,100,94,89,162,8,44,36,54,9,226,12, -11,2,3,33,59,23,195,1,23,196,1,248,28,248,22,17,80,159,49,45,37, -32,0,89,162,43,36,41,9,222,33,60,80,159,48,58,36,89,162,43,35,50, +27,27,28,248,22,17,80,159,51,46,38,80,159,50,46,38,247,22,19,250,22, +25,248,22,23,23,197,2,80,159,53,45,38,23,196,1,27,248,22,175,14,247, +22,148,12,249,22,3,83,158,40,20,100,94,89,162,8,44,37,55,9,226,12, +11,2,3,33,59,23,195,1,23,196,1,248,28,248,22,17,80,159,50,46,38, +32,0,89,162,44,37,42,9,222,33,60,80,159,49,59,37,89,162,44,36,51, 9,227,13,9,8,4,3,33,61,250,22,143,2,23,197,1,197,10,12,28,28, 248,22,191,7,23,202,1,11,28,248,22,169,6,23,206,2,10,28,248,22,55, 23,206,2,10,28,248,22,68,23,206,2,249,22,175,8,248,22,71,23,208,2, -2,25,11,250,22,143,2,80,159,49,43,37,28,248,22,169,6,23,209,2,249, -22,70,23,210,1,27,28,23,212,2,28,249,22,175,8,23,214,2,80,158,54, -46,87,94,23,212,1,80,158,52,47,27,248,22,181,4,23,214,2,28,248,22, -168,13,23,194,2,91,159,38,11,90,161,38,35,11,248,22,189,13,23,197,1, -87,95,83,160,37,11,80,158,56,46,23,23,83,160,37,11,80,158,56,47,192, +2,25,11,250,22,143,2,80,159,50,44,38,28,248,22,169,6,23,209,2,249, +22,70,23,210,1,27,28,23,212,2,28,249,22,175,8,23,214,2,80,158,55, +47,87,94,23,212,1,80,158,53,48,27,248,22,181,4,23,214,2,28,248,22, +168,13,23,194,2,91,159,39,11,90,161,39,36,11,248,22,189,13,23,197,1, +87,95,83,160,38,11,80,158,57,47,23,23,83,160,38,11,80,158,57,48,192, 192,11,11,28,23,193,2,192,87,94,23,193,1,27,247,22,137,5,28,23,193, 2,192,87,94,23,193,1,247,22,145,14,249,22,70,23,210,1,247,22,146,14, 252,22,129,8,23,208,1,23,207,1,23,205,1,23,203,1,201,12,193,87,96, -83,160,37,11,80,158,35,49,248,80,159,36,57,37,249,22,27,11,80,159,38, -51,37,248,22,160,4,80,159,36,50,37,248,22,136,5,80,159,36,36,36,248, -22,139,13,80,159,36,41,36,83,160,37,11,80,158,35,49,248,80,159,36,57, -37,249,22,27,11,80,159,38,51,37,159,35,20,105,159,35,16,1,11,16,0, -83,158,41,20,103,144,66,35,37,98,111,111,116,29,11,11,11,11,11,10,37, -80,158,35,35,20,105,159,36,16,23,2,1,2,2,30,2,4,72,112,97,116, +83,160,38,11,80,158,36,50,248,80,159,37,58,38,249,22,27,11,80,159,39, +52,38,248,22,160,4,80,159,37,51,38,248,22,136,5,80,159,37,37,37,248, +22,139,13,80,159,37,42,37,83,160,38,11,80,158,36,50,248,80,159,37,58, +38,249,22,27,11,80,159,39,52,38,159,36,20,105,159,36,16,1,11,16,0, +83,158,42,20,103,144,66,35,37,98,111,111,116,29,11,11,11,11,11,10,38, +80,158,36,36,20,105,159,37,16,23,2,1,2,2,30,2,4,72,112,97,116, 104,45,115,116,114,105,110,103,63,10,30,2,4,75,112,97,116,104,45,97,100, 100,45,115,117,102,102,105,120,7,30,2,6,2,7,4,30,2,6,1,23,101, 120,116,101,110,100,45,112,97,114,97,109,101,116,101,114,105,122,97,116,105,111, @@ -664,27 +664,27 @@ 30,2,4,76,110,111,114,109,97,108,45,99,97,115,101,45,112,97,116,104,6, 30,2,4,79,112,97,116,104,45,114,101,112,108,97,99,101,45,115,117,102,102, 105,120,9,2,19,2,20,30,2,18,74,114,101,112,97,114,97,109,101,116,101, -114,105,122,101,5,16,0,16,0,35,16,0,35,16,12,2,11,2,12,2,9, -2,10,2,13,2,14,2,2,2,8,2,1,2,16,2,15,2,17,47,11,11, -38,35,11,11,11,16,2,2,19,2,20,16,2,11,11,16,2,2,19,2,20, -37,37,36,11,11,11,16,0,16,0,16,0,35,35,11,11,11,11,16,0,16, -0,16,0,35,35,16,0,16,15,83,158,35,16,2,89,162,43,36,44,9,223, -0,33,27,80,159,35,58,36,83,158,35,16,2,248,22,188,7,69,115,111,45, -115,117,102,102,105,120,80,159,35,35,36,83,158,35,16,2,89,162,43,37,59, -2,2,223,0,33,33,80,159,35,36,36,83,158,35,16,2,32,0,89,162,8, -44,36,41,2,8,222,192,80,159,35,41,36,83,158,35,16,2,247,22,132,2, -80,159,35,42,36,83,158,35,16,2,247,22,131,2,80,159,35,43,36,83,158, -35,16,2,247,22,66,80,159,35,44,36,83,158,35,16,2,248,22,18,74,109, -111,100,117,108,101,45,108,111,97,100,105,110,103,80,159,35,45,36,83,158,35, -16,2,11,80,158,35,46,83,158,35,16,2,11,80,158,35,47,83,158,35,16, -2,32,0,89,162,43,37,8,25,2,15,222,33,39,80,159,35,48,36,83,158, -35,16,2,11,80,158,35,49,83,158,35,16,2,91,159,37,10,90,161,36,35, -10,11,90,161,36,36,10,83,158,38,20,99,96,2,17,89,162,8,44,36,50, -9,224,2,0,33,40,89,162,43,38,48,9,223,1,33,41,89,162,43,39,8, -32,9,224,2,0,33,62,208,80,159,35,50,36,83,158,35,16,2,89,162,43, -35,44,2,19,223,0,33,63,80,159,35,55,36,83,158,35,16,2,89,162,8, -44,35,44,2,20,223,0,33,64,80,159,35,56,36,96,29,94,2,3,68,35, -37,107,101,114,110,101,108,11,29,94,2,3,69,35,37,109,105,110,45,115,116, -120,11,2,4,2,18,9,9,9,35,0}; - EVAL_ONE_SIZED_STR((char *)expr, 5575); +114,105,122,101,5,16,0,16,0,36,16,0,36,16,12,2,11,2,12,2,9, +2,10,2,13,2,14,2,2,2,8,2,1,2,16,2,15,2,17,48,11,11, +39,36,11,11,11,16,2,2,19,2,20,16,2,11,11,16,2,2,19,2,20, +38,38,37,11,11,11,16,0,16,0,16,0,36,36,11,11,11,11,16,0,16, +0,16,0,36,36,16,0,16,15,83,158,36,16,2,89,162,44,37,45,9,223, +0,33,27,80,159,36,59,37,83,158,36,16,2,248,22,188,7,69,115,111,45, +115,117,102,102,105,120,80,159,36,36,37,83,158,36,16,2,89,162,44,38,8, +24,2,2,223,0,33,33,80,159,36,37,37,83,158,36,16,2,32,0,89,162, +8,44,37,42,2,8,222,192,80,159,36,42,37,83,158,36,16,2,247,22,132, +2,80,159,36,43,37,83,158,36,16,2,247,22,131,2,80,159,36,44,37,83, +158,36,16,2,247,22,66,80,159,36,45,37,83,158,36,16,2,248,22,18,74, +109,111,100,117,108,101,45,108,111,97,100,105,110,103,80,159,36,46,37,83,158, +36,16,2,11,80,158,36,47,83,158,36,16,2,11,80,158,36,48,83,158,36, +16,2,32,0,89,162,44,38,8,25,2,15,222,33,39,80,159,36,49,37,83, +158,36,16,2,11,80,158,36,50,83,158,36,16,2,91,159,38,10,90,161,37, +36,10,11,90,161,37,37,10,83,158,39,20,99,96,2,17,89,162,8,44,37, +51,9,224,2,0,33,40,89,162,44,39,49,9,223,1,33,41,89,162,44,40, +8,32,9,224,2,0,33,62,208,80,159,36,51,37,83,158,36,16,2,89,162, +44,36,45,2,19,223,0,33,63,80,159,36,56,37,83,158,36,16,2,89,162, +8,44,36,45,2,20,223,0,33,64,80,159,36,57,37,96,29,94,2,3,68, +35,37,107,101,114,110,101,108,11,29,94,2,3,69,35,37,109,105,110,45,115, +116,120,11,2,4,2,18,9,9,9,36,0}; + EVAL_ONE_SIZED_STR((char *)expr, 5576); } diff --git a/src/mzscheme/src/eval.c b/src/mzscheme/src/eval.c index 479584551e..4fbb6907fd 100644 --- a/src/mzscheme/src/eval.c +++ b/src/mzscheme/src/eval.c @@ -5188,6 +5188,7 @@ static Scheme_Object *sfs_let_one(Scheme_Object *o, SFS_Info *info) Scheme_Let_One *lo = (Scheme_Let_One *)o; Scheme_Object *body, *rhs, *vec; int pos, save_mnt, ip, et; + int unused = 0; scheme_sfs_start_sequence(info, 2, 1); @@ -5228,25 +5229,30 @@ static Scheme_Object *sfs_let_one(Scheme_Object *o, SFS_Info *info) info->max_nontail = save_mnt; if (info->max_used[pos] <= ip) { - /* No one is using it, so either don't push the real value, or - clear it if there's a later non-tail call. + /* No one is using it, so don't actually push the value at run time + (but keep the check that the result is single-valued). The optimizer normally would have converted away the binding, but it might not because (1) it was introduced late by inlining, or (2) the rhs expression doesn't always produce a single value. */ if (scheme_omittable_expr(rhs, 1, -1, 1, NULL)) { rhs = scheme_false; - } else if (ip < info->max_calls[pos]) { - Scheme_Object *clr; + } else if ((ip < info->max_calls[pos]) + && SAME_TYPE(SCHEME_TYPE(rhs), scheme_toplevel_type)) { + /* Unusual case: we can't just drop the global-variable access, + because it might be undefined, but we don't need the value, + and we want to avoid an SFS clear in the interpreter loop. + So, bind #f and then access in the global in a `begin'. */ Scheme_Sequence *s; s = malloc_sequence(2); s->so.type = scheme_sequence_type; s->count = 2; - clr = scheme_make_local(scheme_local_type, 0, SCHEME_LOCAL_CLEAR_ON_READ); - s->array[0] = clr; + s->array[0] = rhs; s->array[1] = body; body = (Scheme_Object *)s; + rhs = scheme_false; } + unused = 1; } } @@ -5254,7 +5260,9 @@ static Scheme_Object *sfs_let_one(Scheme_Object *o, SFS_Info *info) lo->body = body; et = scheme_get_eval_type(lo->value); - SCHEME_LET_EVAL_TYPE(lo) = (et | (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM)); + SCHEME_LET_EVAL_TYPE(lo) = (et + | (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM) + | (unused ? LET_ONE_UNUSED : 0)); return o; } @@ -9817,6 +9825,10 @@ scheme_do_eval(Scheme_Object *obj, int num_rands, Scheme_Object **rands, PUSH_RUNSTACK(p, RUNSTACK, 1); RUNSTACK_CHANGED(); + /* SFS pass may set LET_ONE_UNUSED, but not for the + variable cases; in the constant case, the constant + is #f, so it's ok to push it anyway. */ + switch (SCHEME_LET_EVAL_TYPE(lo) & 0x7) { case SCHEME_EVAL_CONSTANT: RUNSTACK[0] = lo->value; @@ -9840,7 +9852,8 @@ scheme_do_eval(Scheme_Object *obj, int num_rands, Scheme_Object **rands, GC_CAN_IGNORE Scheme_Object *val; SFS_CLEAR_RUNSTACK_ONE(RUNSTACK, 0); val = _scheme_eval_linked_expr_wp(lo->value, p); - RUNSTACK[0] = val; + if (!(SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_UNUSED)) + RUNSTACK[0] = val; } break; } @@ -12324,7 +12337,9 @@ void scheme_validate_expr(Mz_CPort *port, Scheme_Object *expr, scheme_ill_formed_code(port); #endif - if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM) { + if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_UNUSED) { + stack[delta] = VALID_NOT; + } else if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM) { stack[delta] = VALID_FLONUM; /* FIXME: need to check that lo->value produces a flonum */ } else diff --git a/src/mzscheme/src/jit.c b/src/mzscheme/src/jit.c index a8acf27d4e..838bb994c5 100644 --- a/src/mzscheme/src/jit.c +++ b/src/mzscheme/src/jit.c @@ -10109,7 +10109,7 @@ static int generate(Scheme_Object *obj, mz_jit_state *jitter, int is_tail, int m case scheme_let_one_type: { Scheme_Let_One *lv = (Scheme_Let_One *)obj; - int flonum, to_unbox = 0; + int flonum, to_unbox = 0, unused; START_JIT_DATA(); LOG_IT(("leto...\n")); @@ -10126,6 +10126,7 @@ static int generate(Scheme_Object *obj, mz_jit_state *jitter, int is_tail, int m #else flonum = 0; #endif + unused = SCHEME_LET_EVAL_TYPE(lv) & LET_ONE_UNUSED; PAUSE_JIT_DATA(); if (flonum) { @@ -10141,15 +10142,20 @@ static int generate(Scheme_Object *obj, mz_jit_state *jitter, int is_tail, int m generate_unboxed(lv->value, jitter, 1, 0); } #endif + } else if (unused && SCHEME_FALSEP(lv->value)) { + /* unused constants are collapsed to #f by the bytecde compiler */ } else - generate_non_tail(lv->value, jitter, 0, 1, 0); /* no sync */ + generate_non_tail(lv->value, jitter, 0, 1, unused); /* no sync */ + RESUME_JIT_DATA(); CHECK_LIMIT(); - mz_runstack_unskipped(jitter, 1); - - mz_rs_dec(1); - CHECK_RUNSTACK_OVERFLOW(); + if (!unused) { + mz_runstack_unskipped(jitter, 1); + + mz_rs_dec(1); + CHECK_RUNSTACK_OVERFLOW(); + } if (flonum) { #ifdef USE_FLONUM_UNBOXING @@ -10162,17 +10168,19 @@ static int generate(Scheme_Object *obj, mz_jit_state *jitter, int is_tail, int m (void)jit_movi_p(JIT_R0, NULL); #endif } else { - mz_runstack_pushed(jitter, 1); + if (!unused) + mz_runstack_pushed(jitter, 1); } - mz_rs_str(JIT_R0); - + if (!unused) { + mz_rs_str(JIT_R0); + mz_RECORD_STATUS(mz_RS_R0_HAS_RUNSTACK0); + } + END_JIT_DATA(17); LOG_IT(("...in\n")); - mz_RECORD_STATUS(mz_RS_R0_HAS_RUNSTACK0); - if (to_unbox) jitter->unbox = to_unbox; diff --git a/src/mzscheme/src/print.c b/src/mzscheme/src/print.c index a88ed94ae1..2ff5f6e69d 100644 --- a/src/mzscheme/src/print.c +++ b/src/mzscheme/src/print.c @@ -2710,7 +2710,9 @@ print(Scheme_Object *obj, int notdisplay, int compact, Scheme_Hash_Table *ht, lo = (Scheme_Let_One *)obj; - if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM) + if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_UNUSED) + print_compact(pp, CPT_LET_ONE_UNUSED); + else if (SCHEME_LET_EVAL_TYPE(lo) & LET_ONE_FLONUM) print_compact(pp, CPT_LET_ONE_FLONUM); else print_compact(pp, CPT_LET_ONE); diff --git a/src/mzscheme/src/read.c b/src/mzscheme/src/read.c index 60d842e04a..2c5854b9c4 100644 --- a/src/mzscheme/src/read.c +++ b/src/mzscheme/src/read.c @@ -4840,6 +4840,7 @@ static Scheme_Object *read_compact(CPort *port, int use_stack) break; case CPT_LET_ONE: case CPT_LET_ONE_FLONUM: + case CPT_LET_ONE_UNUSED: { Scheme_Let_One *lo; int et; @@ -4854,6 +4855,8 @@ static Scheme_Object *read_compact(CPort *port, int use_stack) et = scheme_get_eval_type(lo->value); if (ch == CPT_LET_ONE_FLONUM) et |= LET_ONE_FLONUM; + if (ch == CPT_LET_ONE_UNUSED) + et |= LET_ONE_UNUSED; SCHEME_LET_EVAL_TYPE(lo) = et; return (Scheme_Object *)lo; diff --git a/src/mzscheme/src/schcpt.h b/src/mzscheme/src/schcpt.h index 98254548dc..4370f09f0f 100644 --- a/src/mzscheme/src/schcpt.h +++ b/src/mzscheme/src/schcpt.h @@ -35,10 +35,11 @@ enum { CPT_CLOSURE, CPT_DELAY_REF, CPT_PREFAB, + CPT_LET_ONE_UNUSED, _CPT_COUNT_ }; -#define CPT_SMALL_NUMBER_START 35 +#define CPT_SMALL_NUMBER_START 36 #define CPT_SMALL_NUMBER_END 60 #define CPT_SMALL_SYMBOL_START 60 diff --git a/src/mzscheme/src/schpriv.h b/src/mzscheme/src/schpriv.h index 1ae4b99f25..09ce487800 100644 --- a/src/mzscheme/src/schpriv.h +++ b/src/mzscheme/src/schpriv.h @@ -1134,13 +1134,14 @@ typedef struct Scheme_Let_Value { #define SCHEME_LET_AUTOBOX(lh) MZ_OPT_HASH_KEY(&lh->iso) typedef struct Scheme_Let_One { - Scheme_Inclhash_Object iso; /* keyex used for eval_type + flonum (and can't be hashed) */ + Scheme_Inclhash_Object iso; /* keyex used for eval_type + flonum/unused (and can't be hashed) */ Scheme_Object *value; Scheme_Object *body; } Scheme_Let_One; #define SCHEME_LET_EVAL_TYPE(lh) MZ_OPT_HASH_KEY(&lh->iso) #define LET_ONE_FLONUM 0x8 +#define LET_ONE_UNUSED 0x10 typedef struct Scheme_Let_Void { Scheme_Inclhash_Object iso; /* keyex used for autobox */ diff --git a/src/mzscheme/src/schvers.h b/src/mzscheme/src/schvers.h index 50251fd7d1..4c3f6ce609 100644 --- a/src/mzscheme/src/schvers.h +++ b/src/mzscheme/src/schvers.h @@ -13,12 +13,12 @@ consistently.) */ -#define MZSCHEME_VERSION "4.2.5.5" +#define MZSCHEME_VERSION "4.2.5.6" #define MZSCHEME_VERSION_X 4 #define MZSCHEME_VERSION_Y 2 #define MZSCHEME_VERSION_Z 5 -#define MZSCHEME_VERSION_W 5 +#define MZSCHEME_VERSION_W 6 #define MZSCHEME_VERSION_MAJOR ((MZSCHEME_VERSION_X * 100) + MZSCHEME_VERSION_Y) #define MZSCHEME_VERSION_MINOR ((MZSCHEME_VERSION_Z * 1000) + MZSCHEME_VERSION_W) diff --git a/src/mzscheme/src/struct.c b/src/mzscheme/src/struct.c index f78b29bdd7..04fa7f81a1 100644 --- a/src/mzscheme/src/struct.c +++ b/src/mzscheme/src/struct.c @@ -2547,11 +2547,14 @@ Scheme_Object *scheme_struct_to_vector(Scheme_Object *_s, Scheme_Object *unknown m++; last_is_unknown = 1; } else { - last_is_unknown = 0; + int count; if (p) - m += stype->num_slots - stype->parent_types[p-1]->num_slots; + count = stype->num_slots - stype->parent_types[p-1]->num_slots; else - m += stype->num_slots; + count = stype->num_slots; + m += count; + if (count) + last_is_unknown = 0; } } @@ -2581,6 +2584,8 @@ Scheme_Object *scheme_struct_to_vector(Scheme_Object *_s, Scheme_Object *unknown i -= n; last_is_unknown = 1; } else { + if (n) + last_is_unknown = 0; while (n--) { --i; if (SAME_OBJ((Scheme_Object *)s, _s)) @@ -2589,7 +2594,6 @@ Scheme_Object *scheme_struct_to_vector(Scheme_Object *_s, Scheme_Object *unknown elem = scheme_struct_ref(_s, i); array[1 + (--m)] = elem; } - last_is_unknown = 0; } }