0.8.16.16:
[sbcl.git] / src / code / pprint.lisp
index 43c66d7..8c084d6 100644 (file)
 ;;;; pretty streams
 
 ;;; There are three different units for measuring character positions:
-;;;  COLUMN - offset (if characters) from the start of the current line.
-;;;  INDEX - index into the output buffer.
-;;;  POSN - some position in the stream of characters cycling through
-;;;         the output buffer.
+;;;  COLUMN - offset (if characters) from the start of the current line
+;;;  INDEX  - index into the output buffer
+;;;  POSN   - some position in the stream of characters cycling through
+;;;          the output buffer
 (deftype column ()
   '(and fixnum unsigned-byte))
 ;;; The INDEX type is picked up from the kernel package.
 
 (defconstant default-line-length 80)
 
-(defstruct (pretty-stream (:include sb!kernel:lisp-stream
-                                   (:out #'pretty-out)
-                                   (:sout #'pretty-sout)
-                                   (:misc #'pretty-misc))
+(defstruct (pretty-stream (:include sb!kernel:ansi-stream
+                                   (out #'pretty-out)
+                                   (sout #'pretty-sout)
+                                   (misc #'pretty-misc))
                          (:constructor make-pretty-stream (target))
                          (:copier nil))
   ;; Where the output is going to finally go.
-  (target (required-argument) :type stream)
+  (target (missing-arg) :type stream)
   ;; Line length we should format to. Cached here so we don't have to keep
   ;; extracting it from the target stream.
   (line-length (or *print-right-margin*
@@ -44,7 +44,7 @@
               :type column)
   ;; A simple string holding all the text that has been output but not yet
   ;; printed.
-  (buffer (make-string initial-buffer-size) :type simple-string)
+  (buffer (make-string initial-buffer-size) :type (simple-array character (*)))
   ;; The index into BUFFER where more text should be put.
   (buffer-fill-pointer 0 :type index)
   ;; Whenever we output stuff from the buffer, we shift the remaining noise
   ;; zero, but if we end up with a very long line with no breaks in it we
   ;; might have to output part of it. Then this will no longer be zero.
   (buffer-start-column (or (sb!impl::charpos target) 0) :type column)
-  ;; The line number we are currently on. Used for *print-lines* abrevs and
-  ;; to tell when sections have been split across multiple lines.
+  ;; The line number we are currently on. Used for *PRINT-LINES*
+  ;; abbreviations and to tell when sections have been split across
+  ;; multiple lines.
   (line-number 0 :type index)
+  ;; the value of *PRINT-LINES* captured at object creation time. We
+  ;; use this, instead of the dynamic *PRINT-LINES*, to avoid
+  ;; weirdness like
+  ;;   (let ((*print-lines* 50))
+  ;;     (pprint-logical-block ..
+  ;;       (dotimes (i 10)
+  ;;         (let ((*print-lines* 8))
+  ;;           (print (aref possiblybigthings i) prettystream)))))
+  ;; terminating the output of the entire logical blockafter 8 lines.
+  (print-lines *print-lines* :type (or index null) :read-only t)
   ;; Stack of logical blocks in effect at the buffer start.
   (blocks (list (make-logical-block)) :type list)
   ;; Buffer holding the per-line prefix active at the buffer start.
   ;; Indentation is included in this. The length of this is stored
   ;; in the logical block stack.
-  (prefix (make-string initial-buffer-size) :type simple-string)
+  (prefix (make-string initial-buffer-size) :type (simple-array character (*)))
   ;; Buffer holding the total remaining suffix active at the buffer start.
   ;; The characters are right-justified in the buffer to make it easier
   ;; to output the buffer. The length is stored in the logical block
   ;; stack.
-  (suffix (make-string initial-buffer-size) :type simple-string)
+  (suffix (make-string initial-buffer-size) :type (simple-array character (*)))
   ;; Queue of pending operations. When empty, HEAD=TAIL=NIL. Otherwise,
   ;; TAIL holds the first (oldest) cons and HEAD holds the last (newest)
   ;; cons. Adding things to the queue is basically (setf (cdr head) (list
 
 (defun pretty-out (stream char)
   (declare (type pretty-stream stream)
-          (type base-char char))
+          (type character char))
   (cond ((char= char #\newline)
         (enqueue-newline stream :literal))
        (t
           (type simple-string string)
           (type index start)
           (type (or index null) end))
-  (let ((end (or end (length string))))
+  (let* ((string (if (typep string '(simple-array character (*)))
+                    string
+                    (coerce string '(simple-array character (*)))))
+        (end (or end (length string))))
     (unless (= start end)
       (let ((newline (position #\newline string :start start :end end)))
        (cond
 
 (defstruct (newline (:include section-start)
                    (:copier nil))
-  (kind (required-argument)
+  (kind (missing-arg)
        :type (member :linear :fill :miser :literal :mandatory)))
 
 (defun enqueue-newline (stream kind)
 
 (defstruct (indentation (:include queued-op)
                        (:copier nil))
-  (kind (required-argument) :type (member :block :current))
+  (kind (missing-arg) :type (member :block :current))
   (amount 0 :type fixnum))
 
 (defun enqueue-indent (stream kind amount)
 (defstruct (block-start (:include section-start)
                        (:copier nil))
   (block-end nil :type (or null block-end))
-  (prefix nil :type (or null simple-string))
-  (suffix nil :type (or null simple-string)))
+  (prefix nil :type (or null (simple-array character (*))))
+  (suffix nil :type (or null (simple-array character (*)))))
 
 (defun start-logical-block (stream prefix per-line-p suffix)
   ;; (In the PPRINT-LOGICAL-BLOCK form which calls us,
   ;; :PREFIX and :PER-LINE-PREFIX have hairy defaulting behavior,
   ;; and might end up being NIL.)
-  (declare (type (or null string prefix)))
+  (declare (type (or null string) prefix))
   ;; (But the defaulting behavior of PPRINT-LOGICAL-BLOCK :SUFFIX is
   ;; trivial, so it should always be a string.)
   (declare (type string suffix))
   (when prefix
+    (setq prefix (coerce prefix '(simple-array character (*))))
     (pretty-sout stream prefix 0 (length prefix)))
   (let* ((pending-blocks (pretty-stream-pending-blocks stream))
         (start (enqueue stream block-start
                         :prefix (and per-line-p prefix)
-                        :suffix suffix
+                        :suffix (coerce suffix '(simple-array character (*)))
                         :depth (length pending-blocks))))
     (setf (pretty-stream-pending-blocks stream)
          (cons start pending-blocks))))
 
 (defstruct (block-end (:include queued-op)
                      (:copier nil))
-  (suffix nil :type (or null simple-string)))
+  (suffix nil :type (or null (simple-array character (*)))))
 
 (defun end-logical-block (stream)
   (let* ((start (pop (pretty-stream-pending-blocks stream)))
 ;;;; tab support
 
 (defun compute-tab-size (tab section-start column)
-  (let ((origin (if (tab-sectionp tab) section-start 0))
-       (colnum (tab-colnum tab))
-       (colinc (tab-colinc tab)))
+  (let* ((origin (if (tab-sectionp tab) section-start 0))
+         (colnum (tab-colnum tab))
+         (colinc (tab-colinc tab))
+         (position (- column origin)))
     (cond ((tab-relativep tab)
           (unless (<= colinc 1)
-            (let ((newposn (+ column colnum)))
+            (let ((newposn (+ position colnum)))
               (let ((rem (rem newposn colinc)))
                 (unless (zerop rem)
                   (incf colnum (- colinc rem))))))
           colnum)
-         ((<= column (+ colnum origin))
-          (- (+ colnum origin) column))
-         (t
+         ((< position colnum)
+           (- colnum position))
+         ((zerop colinc) 0)
+          (t
           (- colinc
-             (rem (- column origin) colinc))))))
+             (rem (- position colnum) colinc))))))
 
 (defun index-column (index stream)
   (let ((column (pretty-stream-buffer-start-column stream))
 
 (defun fits-on-line-p (stream until force-newlines-p)
   (let ((available (pretty-stream-line-length stream)))
-    (when (and (not *print-readably*) *print-lines*
-              (= *print-lines* (pretty-stream-line-number stream)))
+    (when (and (not *print-readably*)
+              (pretty-stream-print-lines stream)
+              (= (pretty-stream-print-lines stream)
+                 (pretty-stream-line-number stream)))
       (decf available 3) ; for the `` ..''
       (decf available (logical-block-suffix-length
                       (car (pretty-stream-blocks stream)))))
     (let ((line-number (pretty-stream-line-number stream)))
       (incf line-number)
       (when (and (not *print-readably*)
-                *print-lines* (>= line-number *print-lines*))
+                (pretty-stream-print-lines stream)
+                (>= line-number (pretty-stream-print-lines stream)))
        (write-string " .." target)
        (let ((suffix-length (logical-block-suffix-length
                              (car (pretty-stream-blocks stream)))))
    *STANDARD-OUTPUT*) if it is a pretty-printing stream, and do
    nothing if not. KIND can be one of:
      :LINEAR - A line break is inserted if and only if the immediatly
-       containing section cannot be printed on one line.
+        containing section cannot be printed on one line.
      :MISER - Same as LINEAR, but only if ``miser-style'' is in effect.
-       (See *PRINT-MISER-WIDTH*.)
+        (See *PRINT-MISER-WIDTH*.)
      :FILL - A line break is inserted if and only if either:
        (a) the following section cannot be printed on the end of the
-          current line,
+           current line,
        (b) the preceding section was not printed on a single line, or
        (c) the immediately containing section cannot be printed on one
-          line and miser-style is in effect.
+           line and miser-style is in effect.
      :MANDATORY - A line break is always inserted.
    When a line break is inserted by any type of conditional newline, any
    blanks that immediately precede the conditional newline are ommitted
   #!+sb-doc
   "Specify the indentation to use in the current logical block if STREAM
    (which defaults to *STANDARD-OUTPUT*) is it is a pretty-printing stream
-   and do nothing if not. (See PPRINT-LOGICAL-BLOCK.)  N is the indention
+   and do nothing if not. (See PPRINT-LOGICAL-BLOCK.)  N is the indentation
    to use (in ems, the width of an ``m'') and RELATIVE-TO can be either:
      :BLOCK - Indent relative to the column the current logical block
-       started on.
+        started on.
      :CURRENT - Indent relative to the current column.
-   The new indention value does not take effect until the following line
+   The new indentation value does not take effect until the following line
    break."
   (declare (type (member :block :current) relative-to)
-          (type integer n)
+          (type real n)
           (type (or stream (member t nil)) stream)
           (values null))
   (let ((stream (case stream
                  ((nil) *standard-output*)
                  (t stream))))
     (when (print-pretty-on-stream-p stream)
-      (enqueue-indent stream relative-to n)))
+      (enqueue-indent stream relative-to (truncate n))))
   nil)
 
 (defun pprint-tab (kind colnum colinc &optional stream)
 (defvar *building-initial-table* nil)
 
 (defstruct (pprint-dispatch-entry (:copier nil))
-  ;; The type specifier for this entry.
-  (type (required-argument) :type t)
-  ;; A function to test to see whether an object is of this time. Pretty must
-  ;; just (lambda (obj) (typep object type)) except that we handle the
-  ;; CONS type specially so that (cons (member foo)) works. We don't
-  ;; bother computing this for entries in the CONS hash table, because
-  ;; we don't need it.
+  ;; the type specifier for this entry
+  (type (missing-arg) :type t)
+  ;; a function to test to see whether an object is of this time.
+  ;; Pretty must just (LAMBDA (OBJ) (TYPEP OBJECT TYPE)) except that
+  ;; we handle the CONS type specially so that (CONS (MEMBER FOO))
+  ;; works. We don't bother computing this for entries in the CONS
+  ;; hash table, because we don't need it.
   (test-fn nil :type (or function null))
-  ;; The priority for this guy.
+  ;; the priority for this guy
   (priority 0 :type real)
   ;; T iff one of the original entries.
   (initial-p *building-initial-table* :type (member t nil))
-  ;; And the associated function.
-  (function (required-argument) :type function))
+  ;; and the associated function
+  (fun (missing-arg) :type callable))
 (def!method print-object ((entry pprint-dispatch-entry) stream)
   (print-unreadable-object (entry stream :type t)
     (format stream "type=~S, priority=~S~@[ [initial]~]"
            (pprint-dispatch-entry-priority entry)
            (pprint-dispatch-entry-initial-p entry))))
 
-(defstruct (pprint-dispatch-table (:copier nil))
-  ;; A list of all the entries (except for CONS entries below) in highest
-  ;; to lowest priority.
-  (entries nil :type list)
-  ;; A hash table mapping things to entries for type specifiers of the
-  ;; form (CONS (MEMBER <thing>)). If the type specifier is of this form,
-  ;; we put it in this hash table instead of the regular entries table.
-  (cons-entries (make-hash-table :test 'eql)))
-(def!method print-object ((table pprint-dispatch-table) stream)
-  (print-unreadable-object (table stream :type t :identity t)))
-
 (defun cons-type-specifier-p (spec)
   (and (consp spec)
        (eq (car spec) 'cons)
             (pprint-dispatch-entry-priority e2)))))
 
 (macrolet ((frob (x)
-            `(cons ',x #'(lambda (object) ,x))))
+            `(cons ',x (lambda (object) ,x))))
   (defvar *precompiled-pprint-dispatch-funs*
     (list (frob (typep object 'array))
          (frob (and (consp object)
-                    (and (typep (car object) 'symbol)
-                         (typep (car object) '(satisfies fboundp)))))
+                    (symbolp (car object))
+                    (fboundp (car object))))
          (frob (typep object 'cons)))))
 
 (defun compute-test-fn (type)
                      (destructuring-bind (type) (cdr type)
                        `(not ,(compute-test-expr type object))))
                     (and
-                     `(and ,@(mapcar #'(lambda (type)
-                                         (compute-test-expr type object))
+                     `(and ,@(mapcar (lambda (type)
+                                       (compute-test-expr type object))
                                      (cdr type))))
                     (or
-                     `(or ,@(mapcar #'(lambda (type)
-                                        (compute-test-expr type object))
+                     `(or ,@(mapcar (lambda (type)
+                                      (compute-test-expr type object))
                                     (cdr type))))
                     (t
                      `(typep ,object ',type)))
       (let ((expr (compute-test-expr type 'object)))
        (cond ((cdr (assoc expr *precompiled-pprint-dispatch-funs*
                           :test #'equal)))
-             ((fboundp 'compile)
-              (compile nil `(lambda (object) ,expr)))
-             (was-cons
-              (warn "CONS PPRINT dispatch ignored w/o compiler loaded:~%  ~S"
-                    type)
-              #'(lambda (object) (declare (ignore object)) nil))
              (t
-              (let ((ttype (sb!kernel:specifier-type type)))
-                #'(lambda (object) (sb!kernel:%typep object ttype)))))))))
+              (compile nil `(lambda (object) ,expr))))))))
 
 (defun copy-pprint-dispatch (&optional (table *print-pprint-dispatch*))
   (declare (type (or pprint-dispatch-table null) table))
         (new (make-pprint-dispatch-table
               :entries (copy-list (pprint-dispatch-table-entries orig))))
         (new-cons-entries (pprint-dispatch-table-cons-entries new)))
-    (maphash #'(lambda (key value)
-                (setf (gethash key new-cons-entries) value))
+    (maphash (lambda (key value)
+              (setf (gethash key new-cons-entries) value))
             (pprint-dispatch-table-cons-entries orig))
     new))
 
            (when (funcall (pprint-dispatch-entry-test-fn entry) object)
              (return entry)))))
     (if entry
-       (values (pprint-dispatch-entry-function entry) t)
-       (values #'(lambda (stream object)
-                   (output-ugly-object object stream))
+       (values (pprint-dispatch-entry-fun entry) t)
+       (values (lambda (stream object)
+                 (output-ugly-object object stream))
                nil))))
 
 (defun set-pprint-dispatch (type function &optional
                            (priority 0) (table *print-pprint-dispatch*))
-  (declare (type (or null function) function)
+  (declare (type (or null callable) function)
           (type real priority)
           (type pprint-dispatch-table table))
+  (/show0 "entering SET-PPRINT-DISPATCH, TYPE=...")
+  (/hexstr type)
   (if function
       (if (cons-type-specifier-p type)
          (setf (gethash (second (second type))
                         (pprint-dispatch-table-cons-entries table))
-               (make-pprint-dispatch-entry :type type :priority priority
-                                           :function function))
+               (make-pprint-dispatch-entry :type type
+                                           :priority priority
+                                           :fun function))
          (let ((list (delete type (pprint-dispatch-table-entries table)
                              :key #'pprint-dispatch-entry-type
                              :test #'equal))
                (entry (make-pprint-dispatch-entry
-                       :type type :test-fn (compute-test-fn type)
-                       :priority priority :function function)))
+                       :type type
+                        :test-fn (compute-test-fn type)
+                        :priority priority
+                        :fun function)))
            (do ((prev nil next)
                 (next list (cdr next)))
                ((null next)
                 (if prev
-                    (setf (cdr prev) (list entry))
-                    (setf list (list entry))))
-             (when (entry< (car next) entry)
-               (if prev
-                   (setf (cdr prev) (cons entry next))
-                   (setf list (cons entry next)))
-               (return)))
+                     (setf (cdr prev) (list entry))
+                     (setf list (list entry))))
+              (when (entry< (car next) entry)
+                (if prev
+                    (setf (cdr prev) (cons entry next))
+                    (setf list (cons entry next)))
+                (return)))
            (setf (pprint-dispatch-table-entries table) list)))
       (if (cons-type-specifier-p type)
          (remhash (second (second type))
                (delete type (pprint-dispatch-table-entries table)
                        :key #'pprint-dispatch-entry-type
                        :test #'equal))))
+  (/show0 "about to return NIL from SET-PPRINT-DISPATCH")
   nil)
 \f
 ;;;; standard pretty-printing routines
             (stringp array)
             (bit-vector-p array))
         (output-ugly-object array stream))
-       ((and *print-readably* (not (eq (array-element-type array) 't)))
+       ((and *print-readably*
+             (not (array-readably-printable-p array)))
         (let ((*print-readably* nil))
           (error 'print-not-readable :object array)))
        ((vectorp array)
                                (index index)
                                (step (reduce #'* dims))
                                (count 0))
-                          (loop                                
+                          (loop
                             (pprint-pop)
                             (output-guts stream index dims)
                             (when (= (incf count) dim)
 
 (defun pprint-lambda-list (stream lambda-list &rest noise)
   (declare (ignore noise))
+  (when (and (consp lambda-list)
+            (member (car lambda-list) *backq-tokens*))
+    ;; if this thing looks like a backquoty thing, then we don't want
+    ;; to destructure it, we want to output it straight away.  [ this
+    ;; is the exception to the normal processing: if we did this
+    ;; generally we would find lambda lists such as (FUNCTION FOO)
+    ;; being printed as #'FOO ]  -- CSR, 2003-12-07
+    (output-object lambda-list stream)
+    (return-from pprint-lambda-list nil))
   (pprint-logical-block (stream lambda-list :prefix "(" :suffix ")")
     (let ((state :required)
          (first t))
     (pprint-fill stream (pprint-pop))
     (pprint-tagbody-guts stream)))
 
-(defun pprint-function-call (stream list &rest noise)
+(defun pprint-fun-call (stream list &rest noise)
   (declare (ignore noise))
   (funcall (formatter "~:<~^~W~^ ~:_~:I~@{~W~^ ~_~}~:>")
           stream
 \f
 ;;;; the interface seen by regular (ugly) printer and initialization routines
 
-;;; OUTPUT-PRETTY-OBJECT is called by OUTPUT-OBJECT when *PRINT-PRETTY* is
-;;; bound to T.
+;;; OUTPUT-PRETTY-OBJECT is called by OUTPUT-OBJECT when
+;;; *PRINT-PRETTY* is true.
 (defun output-pretty-object (object stream)
   (with-pretty-stream (stream)
     (funcall (pprint-dispatch object) stream object)))
     ;; printers for regular types
     (/show0 "doing SET-PPRINT-DISPATCH for regular types")
     (set-pprint-dispatch 'array #'pprint-array)
-    (set-pprint-dispatch '(cons (and symbol (satisfies fboundp)))
-                        #'pprint-function-call -1)
+    (set-pprint-dispatch '(cons symbol)
+                        #'pprint-fun-call -1)
     (set-pprint-dispatch 'cons #'pprint-fill -2)
     ;; cons cells with interesting things for the car
     (/show0 "doing SET-PPRINT-DISPATCH for CONS with interesting CAR")
     (/show0 "leaving !PPRINT-COLD-INIT"))
 
   (setf *print-pprint-dispatch* (copy-pprint-dispatch nil))
-  (setf *pretty-printer* #'output-pretty-object)
   (setf *print-pretty* t))