;;; The contents of this file are subject to the Mozilla Public ;;; License Version 1.1 (the "License"); you may not use this file ;;; except in compliance with the License. You may obtain a copy of ;;; the License at http://www.mozilla.org/MPL/ ;;; ;;; Software distributed under the License is distributed on an "AS ;;; IS" basis, WITHOUT WARRANTY OF ANY KIND, either express or ;;; implied. See the License for the specific language governing ;;; rights and limitations under the License. ;;; ;;; The Original Code is the Language Design and Prototyping Environment. ;;; ;;; The Initial Developer of the Original Code is Netscape Communications ;;; Corporation. Portions created by Netscape Communications Corporation are ;;; Copyright (C) 1999 Netscape Communications Corporation. All ;;; Rights Reserved. ;;; ;;; Contributor(s): Waldemar Horwat ;;; ;;; ECMAScript semantic calculus markup emitters ;;; ;;; Waldemar Horwat (waldemar@acm.org) ;;; (defvar *hide-$-nonterminals* t) ; Should rules and actions expanding nonterminals starting with $ be invisible? (defvar *depict-trivial-functions-as-expressions* nil) (defvar *styled-text-world*) (defun hidden-nonterminal? (general-nonterminal) (and *hide-$-nonterminals* (eql (first-symbol-char (general-grammar-symbol-symbol general-nonterminal)) #\$))) ; Return true if this action call should be replaced by a plain reference to the action's nonterminal. (defun default-action? (action-name) (equal (symbol-name action-name) "$DEFAULT-ACTION")) ;;; ------------------------------------------------------------------------------------------------------ ;;; SEMANTIC DEPICTION UTILITIES (defparameter *semantic-keywords* '(not and or xor mod new eltof some every satisfies such that tag tuple record proc begin end nothing if then elsif else while do return throw try catch case of)) ; Emit markup for one of the semantic keywords, as specified by keyword-symbol. ; space can be either nil, :before, or :after to indicate space placement. (defun depict-semantic-keyword (markup-stream keyword-symbol space) (assert-true (and (member keyword-symbol *semantic-keywords*) (member space '(nil :before :after)))) (when (eq space :before) (depict-space markup-stream)) (depict-char-style (markup-stream :semantic-keyword) (depict markup-stream (string-downcase (symbol-name keyword-symbol)))) (when (eq space :after) (depict-space markup-stream))) ; If test is true, depict an opening parenthesis, evaluate body, and depict a closing ; parentheses. Otherwise, just evaluate body. ; Return the result value of body. (defmacro depict-optional-parentheses ((markup-stream test) &body body) (let ((temp (gensym "PAREN"))) `(let ((,temp ,test)) (when ,temp (depict ,markup-stream "(")) (prog1 (progn ,@body) (when ,temp (depict ,markup-stream ")")))))) ;;; ------------------------------------------------------------------------------------------------------ ;;; DEPICT-ENV ; A depict-env holds state that helps in depicting a grammar or lexer. (defstruct (depict-env (:constructor make-depict-env (visible-semantics heading-offset))) (visible-semantics t :type bool :read-only t) ;Nil if semantics are not to be depicted (heading-offset 0 :type integer :read-only t) ;Offset to be added to each heading level when depicting it (grammar-info nil :type (or null grammar-info)) ;The current grammar-info or nil if none (seen-nonterminals nil :type (or null hash-table)) ;Hash table (nonterminal -> t) of nonterminals already depicted (seen-grammar-arguments nil :type (or null hash-table)) ;Hash table (grammar-argument -> t) of grammar-arguments already depicted (mode nil :type (member nil :syntax :semantics)) ;Current heading (:syntax or :semantics) or nil if none (pending-actions-reverse nil :type list)) ;Reverse-order list of (action-name . closure) of actions pending for a %print-actions (defun checked-depict-env-grammar-info (depict-env) (or (depict-env-grammar-info depict-env) (error "Grammar needed"))) ; Set the mode to the given mode without emitting any headings. ; Return true if the contents should be visible, nil if not. (defun quiet-depict-mode (depict-env mode) (unless (member mode '(nil :syntax :semantics)) (error "Bad mode: ~S" mode)) (setf (depict-env-mode depict-env) mode) (or (depict-env-visible-semantics depict-env) (not (eq mode :semantics)))) ; Set the mode to the given mode, emitting a heading if necessary. ; Return true if the contents should be visible, nil if not. (defun depict-mode (markup-stream depict-env mode) (unless (eq mode (depict-env-mode depict-env)) (when (depict-env-visible-semantics depict-env) (ecase mode (:syntax (depict-paragraph (markup-stream :grammar-header) (depict markup-stream "Syntax"))) (:semantics (depict-paragraph (markup-stream :grammar-header) (depict markup-stream "Semantics"))) ((nil))))) (quiet-depict-mode depict-env mode)) ; Set the mode to :semantics, always emitting a heading with the given group-name string. ; Return true if the contents should be visible, nil if not. (defun depict-semantic-group (markup-stream depict-env group-name) (cond ((depict-env-visible-semantics depict-env) (depict-paragraph (markup-stream :grammar-header) (depict markup-stream group-name)) (setf (depict-env-mode depict-env) :semantics) t) (t nil))) ; Emit markup paragraphs for a command. (defun depict-command (markup-stream world depict-env command) (handler-bind ((error #'(lambda (condition) (declare (ignore condition)) (format *error-output* "~&While depicting: ~:W~%" command)))) (let ((depictor (and (consp command) (identifier? (first command)) (get (world-intern world (first command)) :depict-command)))) (if depictor (apply depictor markup-stream world depict-env (rest command)) (error "Bad command: ~S" command))))) ; Emit markup paragraphs for a list of commands. (defun depict-commands (markup-stream world depict-env commands) (dolist (command commands) (depict-command markup-stream world depict-env command))) ; Emit markup paragraphs for the world's commands. (defun depict-world-commands (markup-stream world &key (visible-semantics t) (heading-offset 0)) (let ((depict-env (make-depict-env visible-semantics heading-offset))) (depict-commands markup-stream world depict-env (world-commands-source world)) (depict-clear-grammar markup-stream world depict-env))) ;;; ------------------------------------------------------------------------------------------------------ ;;; DEPICTING TAGS (defparameter *tag-name-special-cases* '((:+zero "PlusZero" "+zero") (:-zero "MinusZero" (:minus "zero")) (:+infinity "PlusInfinity" ("+" :infinity)) (:-infinity "MinusInfinity" (:minus :infinity)) (:nan "NaN" "NaN"))) ; Return two values: ; A string to use as the tag's link name; ; A depict item or list of items forming the tag's name. (defun tag-link-name-and-name (tag) (let ((special-case (assoc (tag-keyword tag) *tag-name-special-cases*))) (if special-case (values (second special-case) (third special-case)) (let ((name (symbol-lower-mixed-case-name (tag-name tag)))) (values name name))))) ; Emit markup for a tag. ; link should be one of: ; :reference if this is a reference or external reference of this tag; ; :definition if this is a definition of this tag; ; nil if this use of the tag should not be cross-referenced. (defun depict-tag-name (markup-stream tag link) (assert-true (tag-keyword tag)) (when (eq link :reference) (setq link (tag-link tag))) (multiple-value-bind (link-name name) (tag-link-name-and-name tag) (depict-link (markup-stream link "T-" link-name nil) (depict-char-style (markup-stream :tag-name) (depict-item-or-list markup-stream name))))) ; Emit markup for a tuple or record type's label, which must be a symbol. ; link should be one of: ; :reference if this is a reference or external reference to this label; ; nil if this use of the label should not be cross-referenced. (defun depict-label-name (markup-stream type label link) (unless (type-has-field type label) (error "Type ~A doesn't have label ~A" type label)) (let ((type-name (type-name type))) (unless type-name ;(warn "Accessing field ~A of anonymous type ~S" label type) (setq link nil)) (depict-link (markup-stream link "D-" (symbol-upper-mixed-case-name type-name) nil) (depict-char-style (markup-stream :field-name) (depict markup-stream (symbol-lower-mixed-case-name label)))))) ;;; ------------------------------------------------------------------------------------------------------ ;;; DEPICTING TYPES ;;; The level argument indicates what kinds of component types may be represented without being placed ;;; in parentheses. (defparameter *type-level* (make-partial-order)) (def-partial-order-element *type-level* %%primary%%) ;id, tuple, (type) (def-partial-order-element *type-level* %%suffix%% %%primary%%) ;type[], type{} (def-partial-order-element *type-level* %%function%% %%suffix%%) ;type x type -> type (def-partial-order-element *type-level* %%type%% %%function%%) ;type U type ; Emit markup for the name of a type, which must be a symbol. ; link should be one of: ; :reference if this is a reference of this type name; ; :external if this is an external reference of this type name; ; :definition if this is a definition of this type name; ; nil if this use of the type name should not be cross-referenced. (defun depict-type-name (markup-stream type-name link) (let ((name (symbol-upper-mixed-case-name type-name))) (depict-link (markup-stream link "D-" name nil) (depict-char-style (markup-stream :domain-name) (depict markup-stream name))))) ; If level < threshold, depict an opening parenthesis, evaluate body, and depict a closing ; parentheses. Otherwise, just evaluate body. ; Return the result value of body. (defmacro depict-type-parentheses ((markup-stream level threshold) &body body) `(depict-optional-parentheses (,markup-stream (partial-order-< ,level ,threshold)) ,@body)) ; Emit markup for the given type expression. level is non-nil if this is a recursive ; call to depict-type-expr; in this case level indicates the binding level imposed by the ; enclosing type expression. (defun depict-type-expr (markup-stream world type-expr &optional level) (cond ((identifier? type-expr) (let ((type-name (world-intern world type-expr))) (depict-type-name markup-stream type-expr (if (symbol-type-user-defined type-name) :reference :external)))) ((consp type-expr) (let ((depictor (get (world-intern world (first type-expr)) :depict-type-constructor))) (apply depictor markup-stream world (or level %%type%%) (rest type-expr)))) (t (error "Bad type expression: ~S" type-expr)))) ; (-> ( ... ) ) ; " x ... x -> " (defun depict--> (markup-stream world level arg-type-exprs result-type-expr) (depict-type-parentheses (markup-stream level %%function%%) (depict-list markup-stream #'(lambda (markup-stream arg-type-expr) (depict-type-expr markup-stream world arg-type-expr %%suffix%%)) arg-type-exprs :separator '(" " :cartesian-product-10 " ") :empty "()") (depict markup-stream " " :function-arrow-10 " ") (if (eq result-type-expr 'void) (depict markup-stream "()") (depict-type-expr markup-stream world result-type-expr %%suffix%%)))) ; (vector ) ; "[]" (defun depict-vector (markup-stream world level element-type-expr) (depict-type-parentheses (markup-stream level %%suffix%%) (depict-type-expr markup-stream world element-type-expr %%suffix%%) (depict markup-stream "[]"))) ; (range-set ) ; "{}" (defun depict-set (markup-stream world level element-type-expr) (depict-type-parentheses (markup-stream level %%suffix%%) (depict-type-expr markup-stream world element-type-expr %%suffix%%) (depict markup-stream "{}"))) ; (tag ... ) ; "{ *, ..., *}" (defun depict-tag-type (markup-stream world level &rest tag-names) (declare (ignore level)) (depict-list markup-stream #'(lambda (markup-stream tag-name) (depict-tag-name markup-stream (scan-tag world tag-name) :reference)) tag-names :indent 1 :prefix "{" :suffix "}" :separator "," :break 1)) ; (union ... ) ; " U ... U " ; "{}" if no types are given (defun depict-union (markup-stream world level &rest type-exprs) (cond ((endp type-exprs) (depict markup-stream "{}")) ((endp (cdr type-exprs)) (depict-type-expr markup-stream world (first type-exprs) level)) (t (depict-type-parentheses (markup-stream level %%type%%) (depict-list markup-stream #'(lambda (markup-stream type-expr) (depict-type-expr markup-stream world type-expr %%function%%)) type-exprs :indent 0 :separator '(" " :union-10) :break 1))))) ; (writable-cell ) ; "" (defun depict-writable-cell (markup-stream world level element-type-expr) (depict-type-expr markup-stream world element-type-expr level)) ;;; ------------------------------------------------------------------------------------------------------ ;;; DEPICTING EXPRESSIONS ;;; The level argument indicates what kinds of subexpressions may be represented without being placed ;;; in parentheses (or on a separate line for the case of function and if/then/else). ; If primitive-level is not a superset of threshold, depict an opening parenthesis, ; evaluate body, and depict a closing parentheses. Otherwise, just evaluate body. ; Return the result value of body. (defmacro depict-expr-parentheses ((markup-stream primitive-level threshold) &body body) `(depict-optional-parentheses (,markup-stream (partial-order-< ,primitive-level ,threshold)) ,@body)) ; Emit markup for the name of a global variable, which must be a symbol. ; link should be one of: ; :reference if this is a reference of this global variable; ; :external if this is an external reference of this global variable; ; :definition if this is a definition of this global variable; ; nil if this use of the global variable should not be cross-referenced. (defun depict-global-variable (markup-stream global-name link) (let ((name (symbol-lower-mixed-case-name global-name))) (depict-link (markup-stream link "V-" name nil) (depict-char-style (markup-stream :global-variable) (depict markup-stream name))))) ; Emit markup for the name of a local variable, which must be a symbol. (defun depict-local-variable (markup-stream name) (depict-char-style (markup-stream :variable) (depict markup-stream (symbol-lower-mixed-case-name name)))) ; Emit markup for the name of an action, which must be a symbol. (defun depict-action-name (markup-stream action-name) (depict-char-style (markup-stream :action-name) (depict markup-stream (symbol-upper-mixed-case-name action-name)))) ; Emit markup for the value constant. (defun depict-constant (markup-stream constant) (cond ((integerp constant) (depict-integer markup-stream constant)) ((floatp constant) (depict markup-stream (if (zerop constant) (if (minusp (float64-sign constant)) "-0.0" "+0.0") (progn (when (minusp constant) (depict markup-stream :minus) (setq constant (- constant))) (format nil (if (= constant (floor constant 1)) "~,1F" "~F") constant))))) ((characterp constant) (depict markup-stream :left-single-quote) (depict-char-style (markup-stream :character-literal) (depict-character markup-stream constant nil)) (depict markup-stream :right-single-quote)) ((stringp constant) (depict-string markup-stream constant)) (t (error "Bad constant ~S" constant)))) ; Emit markup for the primitive when it is not called in a function call. (defun depict-primitive (markup-stream primitive) (unless (eq (primitive-appearance primitive) :global) (error "Can't depict primitive ~S outside a call" primitive)) (let ((markup (primitive-markup1 primitive)) (external-name (primitive-markup2 primitive))) (if external-name (depict-link (markup-stream :external "V-" external-name nil) (depict-item-or-group-list markup-stream markup)) (depict-item-or-group-list markup-stream markup)))) ; Emit markup for the parameters to a function call. (defun depict-call-parameters (markup-stream world annotated-parameters) (depict-list markup-stream #'(lambda (markup-stream parameter) (depict-expression markup-stream world parameter %expr%)) annotated-parameters :indent 4 :prefix "(" :suffix ")" :separator "," :break 1 :empty nil)) ; Emit markup for the function or primitive call. level indicates the binding level imposed ; by the enclosing expression. (defun depict-call (markup-stream world level annotated-function-expr &rest annotated-arg-exprs) (if (eq (first annotated-function-expr) 'expr-annotation:primitive) (let ((primitive (symbol-primitive (second annotated-function-expr)))) (depict-expr-parentheses (markup-stream level (primitive-level primitive)) (ecase (primitive-appearance primitive) (:global (depict-primitive markup-stream primitive) (depict-call-parameters markup-stream world annotated-arg-exprs)) (:infix (assert-true (= (length annotated-arg-exprs) 2)) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world (first annotated-arg-exprs) (primitive-level1 primitive)) (let ((spaces (primitive-markup2 primitive))) (when spaces (depict-space markup-stream)) (depict-item-or-group-list markup-stream (primitive-markup1 primitive)) (when spaces (depict-break markup-stream 1))) (depict-expression markup-stream world (second annotated-arg-exprs) (primitive-level2 primitive)))) (:unary (assert-true (= (length annotated-arg-exprs) 1)) (depict-item-or-group-list markup-stream (primitive-markup1 primitive)) (depict-expression markup-stream world (first annotated-arg-exprs) (primitive-level1 primitive)) (depict-item-or-group-list markup-stream (primitive-markup2 primitive))) (:phantom (assert-true (= (length annotated-arg-exprs) 1)) (depict-expression markup-stream world (first annotated-arg-exprs) level))))) (depict-expr-parentheses (markup-stream level %suffix%) (depict-expression markup-stream world annotated-function-expr %suffix%) (depict-call-parameters markup-stream world annotated-arg-exprs)))) ; Emit markup for the reference to the action on the given general grammar symbol. (defun depict-action-reference (markup-stream action-name general-grammar-symbol &optional index) (let ((action-default (default-action? action-name))) (unless action-default (depict-action-name markup-stream action-name) (depict markup-stream :action-begin)) (depict-general-grammar-symbol markup-stream general-grammar-symbol :reference index) (unless action-default (depict markup-stream :action-end)))) ; Emit markup for the given annotated value expression. level indicates the binding level imposed ; by the enclosing expression. (defun depict-expression (markup-stream world annotated-expr level) (let ((annotation (first annotated-expr)) (args (rest annotated-expr))) (ecase annotation (expr-annotation:constant (depict-constant markup-stream (first args))) (expr-annotation:primitive (depict-primitive markup-stream (symbol-primitive (first args)))) (expr-annotation:tag (depict-tag-name markup-stream (first args) :reference)) (expr-annotation:local (depict-local-variable markup-stream (first args))) (expr-annotation:global (depict-global-variable markup-stream (first args) :reference)) (expr-annotation:call (apply #'depict-call markup-stream world level args)) (expr-annotation:action (apply #'depict-action-reference markup-stream args)) (expr-annotation:special-form (apply (get (first args) :depict-special-form) markup-stream world level (rest args)))))) ;;; ------------------------------------------------------------------------------------------------------ ;;; DEPICTING SPECIAL FORMS ; (bottom) (defun depict-bottom (markup-stream world level) (declare (ignore world level)) (depict markup-stream :bottom-10)) ; (todo) (defun depict-todo (markup-stream world level) (declare (ignore world level)) (depict markup-stream "????")) ; (hex []) (defun depict-hex (markup-stream world level n length) (if (minusp n) (progn (depict markup-stream "-") (depict-hex markup-stream world level (- n) length)) (depict markup-stream (format nil "0x~V,'0X" length n)))) ; (expt ) (defun depict-expt (markup-stream world level base-annotated-expr exponent-annotated-expr) (depict-expr-parentheses (markup-stream level %prefix%) (depict-expression markup-stream world base-annotated-expr %primary%) (depict-char-style (markup-stream :superscript) (depict-expression markup-stream world exponent-annotated-expr %term%)))) ; (= []) ; (/= []) ; (< []) ; (> []) ; (<= []) ; (>= []) (defun depict-comparison (markup-stream world level order annotated-expr1 annotated-expr2) (depict-expr-parentheses (markup-stream level %relational%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world annotated-expr1 %term%) (depict-space markup-stream) (depict markup-stream order) (depict-break markup-stream 1) (depict-expression markup-stream world annotated-expr2 %term%)))) ; (cascade ... ) (defun depict-cascade (markup-stream world level annotated-expr1 &rest orders-and-exprs) (depict-expr-parentheses (markup-stream level %relational%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world annotated-expr1 %term%) (do () ((endp orders-and-exprs)) (depict-space markup-stream) (depict markup-stream (pop orders-and-exprs)) (depict-break markup-stream 1) (depict-expression markup-stream world (pop orders-and-exprs) %term%))))) ; (and ... ) ; (or ... ) ; (xor ... ) (defun depict-and-or-xor (markup-stream world level op annotated-expr &rest annotated-exprs) (if annotated-exprs (depict-expr-parentheses (markup-stream level %logical%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world annotated-expr %relational%) (dolist (annotated-expr annotated-exprs) (depict-semantic-keyword markup-stream op :before) (depict-break markup-stream 1) (depict-expression markup-stream world annotated-expr %relational%)))) (depict-expression markup-stream world annotated-expr level))) ; (lambda (( [:var | :unused]) ... ( [:var | :unused])) . ) (defun depict-lambda (markup-stream world level arg-binding-exprs result-type-expr &rest body-annotated-stmts) (declare (ignore markup-stream world level arg-binding-exprs result-type-expr body-annotated-stmts)) (error "Depiction of raw lambdas not supported")) #| (defun depict-lambda (markup-stream world level arg-binding-exprs result-type-expr &rest body-annotated-stmts) (depict-expr-parentheses (markup-stream level %expr%) (depict-logical-block (markup-stream 0) (depict-semantic-keyword markup-stream 'proc nil) (depict-function-signature markup-stream world arg-binding-exprs result-type-expr t) (depict-function-body markup-stream world nil :statement body-annotated-stmts)))) |# ; (if ) (defun depict-if-expr (markup-stream world level condition-annotated-expr true-annotated-expr false-annotated-expr) (depict-expr-parentheses (markup-stream level %expr%) (depict-expression markup-stream world condition-annotated-expr %logical%) (depict markup-stream " ?") (depict-logical-block (markup-stream 4) (depict-break markup-stream 1) (depict-expression markup-stream world true-annotated-expr %logical%) (depict markup-stream " :") (depict-break markup-stream 1) (depict-expression markup-stream world false-annotated-expr %logical%)))) ;;; Vectors ; (vector ... ) ; (vector-of ... ) (defun depict-vector-expr (markup-stream world level &rest element-annotated-exprs) (declare (ignore level)) (if element-annotated-exprs (depict-list markup-stream #'(lambda (markup-stream element-annotated-expr) (depict-expression markup-stream world element-annotated-expr %expr%)) element-annotated-exprs :indent 1 :prefix :vector-begin :suffix :vector-end :separator "," :break 1) (depict markup-stream :empty-vector))) #| (defun depict-subscript-type-expr (markup-stream world type-expr) (depict-char-style (markup-stream 'sub) (depict-type-expr markup-stream world type-expr))) |# #| (defun depict-special-function (markup-stream world name-str &rest arg-annotated-exprs) (depict-link (markup-stream :external "V-" name-str nil) (depict-char-style (markup-stream :global-variable) (depict markup-stream name-str))) (depict-call-parameters markup-stream world arg-annotated-exprs)) |# ; (nth ) (defun depict-nth (markup-stream world level vector-annotated-expr n-annotated-expr) (depict-expr-parentheses (markup-stream level %suffix%) (depict-expression markup-stream world vector-annotated-expr %suffix%) (depict markup-stream "[") (depict-expression markup-stream world n-annotated-expr %expr%) (depict markup-stream "]"))) ; (subseq []) (defun depict-subseq (markup-stream world level vector-annotated-expr low-annotated-expr high-annotated-expr) (depict-expr-parentheses (markup-stream level %suffix%) (depict-expression markup-stream world vector-annotated-expr %suffix%) (depict-logical-block (markup-stream 4) (depict markup-stream "[") (depict-expression markup-stream world low-annotated-expr %term%) (depict markup-stream " ...") (when high-annotated-expr (depict-break markup-stream 1) (depict-expression markup-stream world high-annotated-expr %term%)) (depict markup-stream "]")))) ; (append ) (defun depict-append (markup-stream world level vector1-annotated-expr vector2-annotated-expr) (depict-expr-parentheses (markup-stream level %term%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world vector1-annotated-expr %term%) (depict markup-stream " " :vector-append) (depict-break markup-stream 1) (depict-expression markup-stream world vector2-annotated-expr %term%)))) ; (set-nth ) (defun depict-set-nth (markup-stream world level vector-annotated-expr n-annotated-expr value-annotated-expr) (depict-expr-parentheses (markup-stream level %suffix%) (depict-expression markup-stream world vector-annotated-expr %suffix%) (depict-logical-block (markup-stream 4) (depict markup-stream "[") (depict-expression markup-stream world n-annotated-expr %term%) (depict markup-stream " \\") (depict-break markup-stream 1) (depict-expression markup-stream world value-annotated-expr %term%) (depict markup-stream "]")))) ;;; Sets ; (list-set ... ) ; (list-set-of ... ) (defun depict-list-set-expr (markup-stream world level &rest element-annotated-exprs) (declare (ignore level)) (depict-list markup-stream #'(lambda (markup-stream element-annotated-expr) (depict-expression markup-stream world element-annotated-expr %expr%)) element-annotated-exprs :indent 1 :prefix "{" :suffix "}" :separator "," :break 1 :empty nil)) ; (range-set-of-ranges ... ) (defun depict-range-set-of-ranges (markup-stream world level &rest element-annotated-exprs) (declare (ignore level)) (labels ((combine-exprs (element-annotated-exprs) (if (endp element-annotated-exprs) nil (acons (first element-annotated-exprs) (second element-annotated-exprs) (combine-exprs (cddr element-annotated-exprs)))))) (depict-list markup-stream #'(lambda (markup-stream element-annotated-expr-range) (let ((element-annotated-expr1 (car element-annotated-expr-range)) (element-annotated-expr2 (cdr element-annotated-expr-range))) (depict-expression markup-stream world element-annotated-expr1 %term%) (when element-annotated-expr2 (depict markup-stream " ...") (depict-break markup-stream 1) (depict-expression markup-stream world element-annotated-expr2 %term%)))) (combine-exprs element-annotated-exprs) :indent 1 :prefix "{" :suffix "}" :separator "," :break 1 :empty nil))) ; (set* ) (defun depict-set* (markup-stream world level set1-annotated-expr set2-annotated-expr) (depict-expr-parentheses (markup-stream level %factor%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world set1-annotated-expr %factor%) (depict markup-stream " " :intersection-10) (depict-break markup-stream 1) (depict-expression markup-stream world set2-annotated-expr %factor%)))) ; (set+ ) (defun depict-set+ (markup-stream world level set1-annotated-expr set2-annotated-expr) (depict-expr-parentheses (markup-stream level %term%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world set1-annotated-expr %term%) (depict markup-stream " " :union-10) (depict-break markup-stream 1) (depict-expression markup-stream world set2-annotated-expr %term%)))) ; (set- ) (defun depict-set- (markup-stream world level set1-annotated-expr set2-annotated-expr) (depict-expr-parentheses (markup-stream level %term%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world set1-annotated-expr %term%) (depict markup-stream " " :minus) (depict-break markup-stream 1) (depict-expression markup-stream world set2-annotated-expr %factor%)))) ; (set-in ) ; (set-not-in ) (defun depict-set-in (markup-stream world level op elt-annotated-expr set-annotated-expr) (depict-expr-parentheses (markup-stream level %relational%) (depict-logical-block (markup-stream 0) (depict-expression markup-stream world elt-annotated-expr %term%) (depict markup-stream " " op) (depict-break markup-stream 1) (depict-expression markup-stream world set-annotated-expr %term%)))) ; (elt-of ) (defun depict-elt-of (markup-stream world level set-annotated-expr) (depict-expr-parentheses (markup-stream level %min-max%) (depict-semantic-keyword markup-stream 'eltof :after) (depict-expression markup-stream world set-annotated-expr %prefix%))) ;;; Vectors or Sets (defun depict-empty-set-or-vector (markup-stream kind) (ecase kind ((:string :vector) (depict markup-stream :empty-vector)) ((:list-set :range-set) (depict markup-stream "{}")))) ; (empty ) (defun depict-empty (markup-stream world level kind vector-annotated-expr) (depict-expr-parentheses (markup-stream level %relational%) (depict-expression markup-stream world vector-annotated-expr %term%) (depict markup-stream " = ") (depict-empty-set-or-vector markup-stream kind))) ; (nonempty ) (defun depict-nonempty (markup-stream world level kind vector-annotated-expr) (depict-expr-parentheses (markup-stream level %relational%) (depict-expression markup-stream world vector-annotated-expr %term%) (depict markup-stream " " :not-equal " ") (depict-empty-set-or-vector markup-stream kind))) ; (length ) (defun depict-length (markup-stream world level vector-annotated-expr) (declare (ignore level)) (depict markup-stream "|") (depict-expression markup-stream world vector-annotated-expr %expr%) (depict markup-stream "|")) ; (some ) ; (every ) (defun depict-some (markup-stream world level keyword collection-annotated-expr var condition-annotated-expr) (depict-expr-parentheses (markup-stream level %expr%) (depict-logical-block (markup-stream 2) (depict-semantic-keyword markup-stream keyword :after) (depict-local-variable markup-stream var) (depict markup-stream " " :member-10 " ") (depict-expression markup-stream world collection-annotated-expr %term%) (depict-semantic-keyword markup-stream 'satisfies :before) (depict-break markup-stream 1) (depict-expression markup-stream world condition-annotated-expr %logical%)))) ; (map []) (defun depict-map (markup-stream world level collection-kind collection-annotated-expr var value-annotated-expr &optional condition-annotated-expr) (declare (ignore level)) (multiple-value-bind (open bar close) (ecase collection-kind ((:string :vector) (values :vector-begin :vector-construct :vector-end)) ((:list-set :range-set) (values "{" "|" "}"))) (depict-logical-block (markup-stream 2) (depict markup-stream open) (depict-expression markup-stream world value-annotated-expr %expr%) (depict markup-stream " " bar) (depict-break markup-stream 1) (depict markup-stream :for-all-10) (depict-local-variable markup-stream var) (depict markup-stream " " :member-10 " ") (depict-expression markup-stream world collection-annotated-expr %term%) (when condition-annotated-expr (depict-semantic-keyword markup-stream 'such :before) (depict-semantic-keyword markup-stream 'that :before) (depict-break markup-stream 1) (depict-expression markup-stream world condition-annotated-expr %logical%)) (depict markup-stream close)))) ;;; Tuples and Records (defparameter *depict-tag-labels* nil) ; (new ... ) (defun depict-new (markup-stream world level type type-name &rest annotated-exprs) (let* ((tag (type-tag type)) (mutable (tag-mutable tag))) (flet ((depict-tag-and-args (markup-stream) (let ((fields (tag-fields tag))) (assert-true (= (length fields) (length annotated-exprs))) (depict-type-name markup-stream type-name :reference) (if (tag-keyword tag) (assert-true (null annotated-exprs)) (depict-list markup-stream #'(lambda (markup-stream parameter) (let ((field (pop fields))) (if (and mutable *depict-tag-labels*) (depict-logical-block (markup-stream 4) (depict-label-name markup-stream (symbol-type (tag-name tag)) (field-label field) :reference) (depict markup-stream " " :label-assign-10) (depict-break markup-stream 1) (depict-expression markup-stream world parameter %expr%)) (depict-expression markup-stream world parameter %expr%)))) annotated-exprs :indent 4 :prefix (if mutable :record-begin :tuple-begin) :suffix (if mutable :record-end :tuple-end) :separator "," :break 1 :empty nil))))) (if mutable (depict-expr-parentheses (markup-stream level %prefix%) (depict-logical-block (markup-stream 4) (depict-semantic-keyword markup-stream 'new :after) (depict-tag-and-args markup-stream))) (depict-tag-and-args markup-stream))))) ; (&