0.6.10.21:
[sbcl.git] / src / code / pprint.lisp
1 ;;;; Common Lisp pretty printer
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!PRETTY")
13 \f
14 ;;;; pretty streams
15
16 ;;; There are three different units for measuring character positions:
17 ;;;  COLUMN - offset (if characters) from the start of the current line.
18 ;;;  INDEX - index into the output buffer.
19 ;;;  POSN - some position in the stream of characters cycling through
20 ;;;          the output buffer.
21 (deftype column ()
22   '(and fixnum unsigned-byte))
23 ;;; The INDEX type is picked up from the kernel package.
24 (deftype posn ()
25   'fixnum)
26
27 (defconstant initial-buffer-size 128)
28
29 (defconstant default-line-length 80)
30
31 (defstruct (pretty-stream (:include sb!kernel:lisp-stream
32                                     (:out #'pretty-out)
33                                     (:sout #'pretty-sout)
34                                     (:misc #'pretty-misc))
35                           (:constructor make-pretty-stream (target)))
36   ;; Where the output is going to finally go.
37   (target (required-argument) :type stream)
38   ;; Line length we should format to. Cached here so we don't have to keep
39   ;; extracting it from the target stream.
40   (line-length (or *print-right-margin*
41                    (sb!impl::line-length target)
42                    default-line-length)
43                :type column)
44   ;; A simple string holding all the text that has been output but not yet
45   ;; printed.
46   (buffer (make-string initial-buffer-size) :type simple-string)
47   ;; The index into BUFFER where more text should be put.
48   (buffer-fill-pointer 0 :type index)
49   ;; Whenever we output stuff from the buffer, we shift the remaining noise
50   ;; over. This makes it difficult to keep references to locations in
51   ;; the buffer. Therefore, we have to keep track of the total amount of
52   ;; stuff that has been shifted out of the buffer.
53   (buffer-offset 0 :type posn)
54   ;; The column the first character in the buffer will appear in. Normally
55   ;; zero, but if we end up with a very long line with no breaks in it we
56   ;; might have to output part of it. Then this will no longer be zero.
57   (buffer-start-column (or (sb!impl::charpos target) 0) :type column)
58   ;; The line number we are currently on. Used for *print-lines* abrevs and
59   ;; to tell when sections have been split across multiple lines.
60   (line-number 0 :type index)
61   ;; Stack of logical blocks in effect at the buffer start.
62   (blocks (list (make-logical-block)) :type list)
63   ;; Buffer holding the per-line prefix active at the buffer start.
64   ;; Indentation is included in this. The length of this is stored
65   ;; in the logical block stack.
66   (prefix (make-string initial-buffer-size) :type simple-string)
67   ;; Buffer holding the total remaining suffix active at the buffer start.
68   ;; The characters are right-justified in the buffer to make it easier
69   ;; to output the buffer. The length is stored in the logical block
70   ;; stack.
71   (suffix (make-string initial-buffer-size) :type simple-string)
72   ;; Queue of pending operations. When empty, HEAD=TAIL=NIL. Otherwise,
73   ;; TAIL holds the first (oldest) cons and HEAD holds the last (newest)
74   ;; cons. Adding things to the queue is basically (setf (cdr head) (list
75   ;; new)) and removing them is basically (pop tail) [except that care must
76   ;; be taken to handle the empty queue case correctly.]
77   (queue-tail nil :type list)
78   (queue-head nil :type list)
79   ;; Block-start queue entries in effect at the queue head.
80   (pending-blocks nil :type list))
81 (def!method print-object ((pstream pretty-stream) stream)
82   ;; FIXME: CMU CL had #+NIL'ed out this code and done a hand-written
83   ;; FORMAT hack instead. Make sure that this code actually works instead
84   ;; of falling into infinite regress or something.
85   (print-unreadable-object (pstream stream :type t :identity t)))
86
87 #!-sb-fluid (declaim (inline index-posn posn-index posn-column))
88 (defun index-posn (index stream)
89   (declare (type index index) (type pretty-stream stream)
90            (values posn))
91   (+ index (pretty-stream-buffer-offset stream)))
92 (defun posn-index (posn stream)
93   (declare (type posn posn) (type pretty-stream stream)
94            (values index))
95   (- posn (pretty-stream-buffer-offset stream)))
96 (defun posn-column (posn stream)
97   (declare (type posn posn) (type pretty-stream stream)
98            (values posn))
99   (index-column (posn-index posn stream) stream))
100 \f
101 ;;;; stream interface routines
102
103 (defun pretty-out (stream char)
104   (declare (type pretty-stream stream)
105            (type base-char char))
106   (cond ((char= char #\newline)
107          (enqueue-newline stream :literal))
108         (t
109          (ensure-space-in-buffer stream 1)
110          (let ((fill-pointer (pretty-stream-buffer-fill-pointer stream)))
111            (setf (schar (pretty-stream-buffer stream) fill-pointer) char)
112            (setf (pretty-stream-buffer-fill-pointer stream)
113                  (1+ fill-pointer))))))
114
115 (defun pretty-sout (stream string start end)
116   (declare (type pretty-stream stream)
117            (type simple-string string)
118            (type index start)
119            (type (or index null) end))
120   (let ((end (or end (length string))))
121     (unless (= start end)
122       (let ((newline (position #\newline string :start start :end end)))
123         (cond
124          (newline
125           (pretty-sout stream string start newline)
126           (enqueue-newline stream :literal)
127           (pretty-sout stream string (1+ newline) end))
128          (t
129           (let ((chars (- end start)))
130             (loop
131               (let* ((available (ensure-space-in-buffer stream chars))
132                      (count (min available chars))
133                      (fill-pointer (pretty-stream-buffer-fill-pointer stream))
134                      (new-fill-ptr (+ fill-pointer count)))
135                 (replace (pretty-stream-buffer stream)
136                          string
137                          :start1 fill-pointer :end1 new-fill-ptr
138                          :start2 start)
139                 (setf (pretty-stream-buffer-fill-pointer stream) new-fill-ptr)
140                 (decf chars count)
141                 (when (zerop count)
142                   (return))
143                 (incf start count))))))))))
144
145 (defun pretty-misc (stream op &optional arg1 arg2)
146   (declare (ignore stream op arg1 arg2)))
147 \f
148 ;;;; logical blocks
149
150 (defstruct logical-block
151   ;; The column this logical block started in.
152   (start-column 0 :type column)
153   ;; The column the current section started in.
154   (section-column 0 :type column)
155   ;; The length of the per-line prefix. We can't move the indentation
156   ;; left of this.
157   (per-line-prefix-end 0 :type index)
158   ;; The overall length of the prefix, including any indentation.
159   (prefix-length 0 :type index)
160   ;; The overall length of the suffix.
161   (suffix-length 0 :type index)
162   ;; The line number
163   (section-start-line 0 :type index))
164
165 (defun really-start-logical-block (stream column prefix suffix)
166   (let* ((blocks (pretty-stream-blocks stream))
167          (prev-block (car blocks))
168          (per-line-end (logical-block-per-line-prefix-end prev-block))
169          (prefix-length (logical-block-prefix-length prev-block))
170          (suffix-length (logical-block-suffix-length prev-block))
171          (block (make-logical-block
172                  :start-column column
173                  :section-column column
174                  :per-line-prefix-end per-line-end
175                  :prefix-length prefix-length
176                  :suffix-length suffix-length
177                  :section-start-line (pretty-stream-line-number stream))))
178     (setf (pretty-stream-blocks stream) (cons block blocks))
179     (set-indentation stream column)
180     (when prefix
181       (setf (logical-block-per-line-prefix-end block) column)
182       (replace (pretty-stream-prefix stream) prefix
183                :start1 (- column (length prefix)) :end1 column))
184     (when suffix
185       (let* ((total-suffix (pretty-stream-suffix stream))
186              (total-suffix-len (length total-suffix))
187              (additional (length suffix))
188              (new-suffix-len (+ suffix-length additional)))
189         (when (> new-suffix-len total-suffix-len)
190           (let ((new-total-suffix-len
191                  (max (* total-suffix-len 2)
192                       (+ suffix-length
193                          (floor (* additional 5) 4)))))
194             (setf total-suffix
195                   (replace (make-string new-total-suffix-len) total-suffix
196                            :start1 (- new-total-suffix-len suffix-length)
197                            :start2 (- total-suffix-len suffix-length)))
198             (setf total-suffix-len new-total-suffix-len)
199             (setf (pretty-stream-suffix stream) total-suffix)))
200         (replace total-suffix suffix
201                  :start1 (- total-suffix-len new-suffix-len)
202                  :end1 (- total-suffix-len suffix-length))
203         (setf (logical-block-suffix-length block) new-suffix-len))))
204   nil)
205
206 (defun set-indentation (stream column)
207   (let* ((prefix (pretty-stream-prefix stream))
208          (prefix-len (length prefix))
209          (block (car (pretty-stream-blocks stream)))
210          (current (logical-block-prefix-length block))
211          (minimum (logical-block-per-line-prefix-end block))
212          (column (max minimum column)))
213     (when (> column prefix-len)
214       (setf prefix
215             (replace (make-string (max (* prefix-len 2)
216                                        (+ prefix-len
217                                           (floor (* (- column prefix-len) 5)
218                                                  4))))
219                      prefix
220                      :end1 current))
221       (setf (pretty-stream-prefix stream) prefix))
222     (when (> column current)
223       (fill prefix #\space :start current :end column))
224     (setf (logical-block-prefix-length block) column)))
225
226 (defun really-end-logical-block (stream)
227   (let* ((old (pop (pretty-stream-blocks stream)))
228          (old-indent (logical-block-prefix-length old))
229          (new (car (pretty-stream-blocks stream)))
230          (new-indent (logical-block-prefix-length new)))
231     (when (> new-indent old-indent)
232       (fill (pretty-stream-prefix stream) #\space
233             :start old-indent :end new-indent)))
234   nil)
235 \f
236 ;;;; the pending operation queue
237
238 (defstruct (queued-op (:constructor nil))
239   (posn 0 :type posn))
240
241 (defmacro enqueue (stream type &rest args)
242   (let ((constructor (symbolicate "MAKE-" type)))
243     (once-only ((stream stream)
244                 (entry `(,constructor :posn
245                                       (index-posn
246                                        (pretty-stream-buffer-fill-pointer
247                                         ,stream)
248                                        ,stream)
249                                       ,@args))
250                 (op `(list ,entry))
251                 (head `(pretty-stream-queue-head ,stream)))
252       `(progn
253          (if ,head
254              (setf (cdr ,head) ,op)
255              (setf (pretty-stream-queue-tail ,stream) ,op))
256          (setf (pretty-stream-queue-head ,stream) ,op)
257          ,entry))))
258
259 (defstruct (section-start (:include queued-op)
260                           (:constructor nil))
261   (depth 0 :type index)
262   (section-end nil :type (or null newline block-end)))
263
264 (defstruct (newline
265             (:include section-start))
266   (kind (required-argument)
267         :type (member :linear :fill :miser :literal :mandatory)))
268
269 (defun enqueue-newline (stream kind)
270   (let* ((depth (length (pretty-stream-pending-blocks stream)))
271          (newline (enqueue stream newline :kind kind :depth depth)))
272     (dolist (entry (pretty-stream-queue-tail stream))
273       (when (and (not (eq newline entry))
274                  (section-start-p entry)
275                  (null (section-start-section-end entry))
276                  (<= depth (section-start-depth entry)))
277         (setf (section-start-section-end entry) newline))))
278   (maybe-output stream (or (eq kind :literal) (eq kind :mandatory))))
279
280 (defstruct (indentation
281             (:include queued-op))
282   (kind (required-argument) :type (member :block :current))
283   (amount 0 :type fixnum))
284
285 (defun enqueue-indent (stream kind amount)
286   (enqueue stream indentation :kind kind :amount amount))
287
288 (defstruct (block-start
289             (:include section-start))
290   (block-end nil :type (or null block-end))
291   (prefix nil :type (or null simple-string))
292   (suffix nil :type (or null simple-string)))
293
294 (defun start-logical-block (stream prefix per-line-p suffix)
295   ;; (In the PPRINT-LOGICAL-BLOCK form which calls us,
296   ;; :PREFIX and :PER-LINE-PREFIX have hairy defaulting behavior,
297   ;; and might end up being NIL.)
298   (declare (type (or null string prefix)))
299   ;; (But the defaulting behavior of PPRINT-LOGICAL-BLOCK :SUFFIX is
300   ;; trivial, so it should always be a string.)
301   (declare (type string suffix))
302   (when prefix
303     (pretty-sout stream prefix 0 (length prefix)))
304   (let* ((pending-blocks (pretty-stream-pending-blocks stream))
305          (start (enqueue stream block-start
306                          :prefix (and per-line-p prefix)
307                          :suffix suffix
308                          :depth (length pending-blocks))))
309     (setf (pretty-stream-pending-blocks stream)
310           (cons start pending-blocks))))
311
312 (defstruct (block-end
313             (:include queued-op))
314   (suffix nil :type (or null simple-string)))
315
316 (defun end-logical-block (stream)
317   (let* ((start (pop (pretty-stream-pending-blocks stream)))
318          (suffix (block-start-suffix start))
319          (end (enqueue stream block-end :suffix suffix)))
320     (when suffix
321       (pretty-sout stream suffix 0 (length suffix)))
322     (setf (block-start-block-end start) end)))
323
324 (defstruct (tab
325             (:include queued-op))
326   (sectionp nil :type (member t nil))
327   (relativep nil :type (member t nil))
328   (colnum 0 :type column)
329   (colinc 0 :type column))
330
331 (defun enqueue-tab (stream kind colnum colinc)
332   (multiple-value-bind (sectionp relativep)
333       (ecase kind
334         (:line (values nil nil))
335         (:line-relative (values nil t))
336         (:section (values t nil))
337         (:section-relative (values t t)))
338     (enqueue stream tab :sectionp sectionp :relativep relativep
339              :colnum colnum :colinc colinc)))
340 \f
341 ;;;; tab support
342
343 (defun compute-tab-size (tab section-start column)
344   (let ((origin (if (tab-sectionp tab) section-start 0))
345         (colnum (tab-colnum tab))
346         (colinc (tab-colinc tab)))
347     (cond ((tab-relativep tab)
348            (unless (<= colinc 1)
349              (let ((newposn (+ column colnum)))
350                (let ((rem (rem newposn colinc)))
351                  (unless (zerop rem)
352                    (incf colnum (- colinc rem))))))
353            colnum)
354           ((<= column (+ colnum origin))
355            (- (+ colnum origin) column))
356           (t
357            (- colinc
358               (rem (- column origin) colinc))))))
359
360 (defun index-column (index stream)
361   (let ((column (pretty-stream-buffer-start-column stream))
362         (section-start (logical-block-section-column
363                         (first (pretty-stream-blocks stream))))
364         (end-posn (index-posn index stream)))
365     (dolist (op (pretty-stream-queue-tail stream))
366       (when (>= (queued-op-posn op) end-posn)
367         (return))
368       (typecase op
369         (tab
370          (incf column
371                (compute-tab-size op
372                                  section-start
373                                  (+ column
374                                     (posn-index (tab-posn op)
375                                                     stream)))))
376         ((or newline block-start)
377          (setf section-start
378                (+ column (posn-index (queued-op-posn op)
379                                          stream))))))
380     (+ column index)))
381
382 (defun expand-tabs (stream through)
383   (let ((insertions nil)
384         (additional 0)
385         (column (pretty-stream-buffer-start-column stream))
386         (section-start (logical-block-section-column
387                         (first (pretty-stream-blocks stream)))))
388     (dolist (op (pretty-stream-queue-tail stream))
389       (typecase op
390         (tab
391          (let* ((index (posn-index (tab-posn op) stream))
392                 (tabsize (compute-tab-size op
393                                            section-start
394                                            (+ column index))))
395            (unless (zerop tabsize)
396              (push (cons index tabsize) insertions)
397              (incf additional tabsize)
398              (incf column tabsize))))
399         ((or newline block-start)
400          (setf section-start
401                (+ column (posn-index (queued-op-posn op) stream)))))
402       (when (eq op through)
403         (return)))
404     (when insertions
405       (let* ((fill-ptr (pretty-stream-buffer-fill-pointer stream))
406              (new-fill-ptr (+ fill-ptr additional))
407              (buffer (pretty-stream-buffer stream))
408              (new-buffer buffer)
409              (length (length buffer))
410              (end fill-ptr))
411         (when (> new-fill-ptr length)
412           (let ((new-length (max (* length 2)
413                                  (+ fill-ptr
414                                     (floor (* additional 5) 4)))))
415             (setf new-buffer (make-string new-length))
416             (setf (pretty-stream-buffer stream) new-buffer)))
417         (setf (pretty-stream-buffer-fill-pointer stream) new-fill-ptr)
418         (decf (pretty-stream-buffer-offset stream) additional)
419         (dolist (insertion insertions)
420           (let* ((srcpos (car insertion))
421                  (amount (cdr insertion))
422                  (dstpos (+ srcpos additional)))
423             (replace new-buffer buffer :start1 dstpos :start2 srcpos :end2 end)
424             (fill new-buffer #\space :start (- dstpos amount) :end dstpos)
425             (decf additional amount)
426             (setf end srcpos)))
427         (unless (eq new-buffer buffer)
428           (replace new-buffer buffer :end1 end :end2 end))))))
429 \f
430 ;;;; stuff to do the actual outputting
431
432 (defun ensure-space-in-buffer (stream want)
433   (declare (type pretty-stream stream)
434            (type index want))
435   (let* ((buffer (pretty-stream-buffer stream))
436          (length (length buffer))
437          (fill-ptr (pretty-stream-buffer-fill-pointer stream))
438          (available (- length fill-ptr)))
439     (cond ((plusp available)
440            available)
441           ((> fill-ptr (pretty-stream-line-length stream))
442            (unless (maybe-output stream nil)
443              (output-partial-line stream))
444            (ensure-space-in-buffer stream want))
445           (t
446            (let* ((new-length (max (* length 2)
447                                    (+ length
448                                       (floor (* want 5) 4))))
449                   (new-buffer (make-string new-length)))
450              (setf (pretty-stream-buffer stream) new-buffer)
451              (replace new-buffer buffer :end1 fill-ptr)
452              (- new-length fill-ptr))))))
453
454 (defun maybe-output (stream force-newlines-p)
455   (declare (type pretty-stream stream))
456   (let ((tail (pretty-stream-queue-tail stream))
457         (output-anything nil))
458     (loop
459       (unless tail
460         (setf (pretty-stream-queue-head stream) nil)
461         (return))
462       (let ((next (pop tail)))
463         (etypecase next
464           (newline
465            (when (ecase (newline-kind next)
466                    ((:literal :mandatory :linear) t)
467                    (:miser (misering-p stream))
468                    (:fill
469                     (or (misering-p stream)
470                         (> (pretty-stream-line-number stream)
471                            (logical-block-section-start-line
472                             (first (pretty-stream-blocks stream))))
473                         (ecase (fits-on-line-p stream
474                                                (newline-section-end next)
475                                                force-newlines-p)
476                           ((t) nil)
477                           ((nil) t)
478                           (:dont-know
479                            (return))))))
480              (setf output-anything t)
481              (output-line stream next)))
482           (indentation
483            (unless (misering-p stream)
484              (set-indentation stream
485                               (+ (ecase (indentation-kind next)
486                                    (:block
487                                     (logical-block-start-column
488                                      (car (pretty-stream-blocks stream))))
489                                    (:current
490                                     (posn-column
491                                      (indentation-posn next)
492                                      stream)))
493                                  (indentation-amount next)))))
494           (block-start
495            (ecase (fits-on-line-p stream (block-start-section-end next)
496                                   force-newlines-p)
497              ((t)
498               ;; Just nuke the whole logical block and make it look
499               ;; like one nice long literal.
500               (let ((end (block-start-block-end next)))
501                 (expand-tabs stream end)
502                 (setf tail (cdr (member end tail)))))
503              ((nil)
504               (really-start-logical-block
505                stream
506                (posn-column (block-start-posn next) stream)
507                (block-start-prefix next)
508                (block-start-suffix next)))
509              (:dont-know
510               (return))))
511           (block-end
512            (really-end-logical-block stream))
513           (tab
514            (expand-tabs stream next))))
515       (setf (pretty-stream-queue-tail stream) tail))
516     output-anything))
517
518 (defun misering-p (stream)
519   (declare (type pretty-stream stream))
520   (and *print-miser-width*
521        (<= (- (pretty-stream-line-length stream)
522               (logical-block-start-column (car (pretty-stream-blocks stream))))
523            *print-miser-width*)))
524
525 (defun fits-on-line-p (stream until force-newlines-p)
526   (let ((available (pretty-stream-line-length stream)))
527     (when (and (not *print-readably*) *print-lines*
528                (= *print-lines* (pretty-stream-line-number stream)))
529       (decf available 3) ; for the `` ..''
530       (decf available (logical-block-suffix-length
531                        (car (pretty-stream-blocks stream)))))
532     (cond (until
533            (<= (posn-column (queued-op-posn until) stream) available))
534           (force-newlines-p nil)
535           ((> (index-column (pretty-stream-buffer-fill-pointer stream) stream)
536               available)
537            nil)
538           (t
539            :dont-know))))
540
541 (defun output-line (stream until)
542   (declare (type pretty-stream stream)
543            (type newline until))
544   (let* ((target (pretty-stream-target stream))
545          (buffer (pretty-stream-buffer stream))
546          (kind (newline-kind until))
547          (literal-p (eq kind :literal))
548          (amount-to-consume (posn-index (newline-posn until) stream))
549          (amount-to-print
550           (if literal-p
551               amount-to-consume
552               (let ((last-non-blank
553                      (position #\space buffer :end amount-to-consume
554                                :from-end t :test #'char/=)))
555                 (if last-non-blank
556                     (1+ last-non-blank)
557                     0)))))
558     (write-string buffer target :end amount-to-print)
559     (let ((line-number (pretty-stream-line-number stream)))
560       (incf line-number)
561       (when (and (not *print-readably*)
562                  *print-lines* (>= line-number *print-lines*))
563         (write-string " .." target)
564         (let ((suffix-length (logical-block-suffix-length
565                               (car (pretty-stream-blocks stream)))))
566           (unless (zerop suffix-length)
567             (let* ((suffix (pretty-stream-suffix stream))
568                    (len (length suffix)))
569               (write-string suffix target
570                             :start (- len suffix-length)
571                             :end len))))
572         (throw 'line-limit-abbreviation-happened t))
573       (setf (pretty-stream-line-number stream) line-number)
574       (write-char #\newline target)
575       (setf (pretty-stream-buffer-start-column stream) 0)
576       (let* ((fill-ptr (pretty-stream-buffer-fill-pointer stream))
577              (block (first (pretty-stream-blocks stream)))
578              (prefix-len
579               (if literal-p
580                   (logical-block-per-line-prefix-end block)
581                   (logical-block-prefix-length block)))
582              (shift (- amount-to-consume prefix-len))
583              (new-fill-ptr (- fill-ptr shift))
584              (new-buffer buffer)
585              (buffer-length (length buffer)))
586         (when (> new-fill-ptr buffer-length)
587           (setf new-buffer
588                 (make-string (max (* buffer-length 2)
589                                   (+ buffer-length
590                                      (floor (* (- new-fill-ptr buffer-length)
591                                                5)
592                                             4)))))
593           (setf (pretty-stream-buffer stream) new-buffer))
594         (replace new-buffer buffer
595                  :start1 prefix-len :start2 amount-to-consume :end2 fill-ptr)
596         (replace new-buffer (pretty-stream-prefix stream)
597                  :end1 prefix-len)
598         (setf (pretty-stream-buffer-fill-pointer stream) new-fill-ptr)
599         (incf (pretty-stream-buffer-offset stream) shift)
600         (unless literal-p
601           (setf (logical-block-section-column block) prefix-len)
602           (setf (logical-block-section-start-line block) line-number))))))
603
604 (defun output-partial-line (stream)
605   (let* ((fill-ptr (pretty-stream-buffer-fill-pointer stream))
606          (tail (pretty-stream-queue-tail stream))
607          (count
608           (if tail
609               (posn-index (queued-op-posn (car tail)) stream)
610               fill-ptr))
611          (new-fill-ptr (- fill-ptr count))
612          (buffer (pretty-stream-buffer stream)))
613     (when (zerop count)
614       (error "Output-partial-line called when nothing can be output."))
615     (write-string buffer (pretty-stream-target stream)
616                   :start 0 :end count)
617     (incf (pretty-stream-buffer-start-column stream) count)
618     (replace buffer buffer :end1 new-fill-ptr :start2 count :end2 fill-ptr)
619     (setf (pretty-stream-buffer-fill-pointer stream) new-fill-ptr)
620     (incf (pretty-stream-buffer-offset stream) count)))
621
622 (defun force-pretty-output (stream)
623   (maybe-output stream nil)
624   (expand-tabs stream nil)
625   (write-string (pretty-stream-buffer stream)
626                 (pretty-stream-target stream)
627                 :end (pretty-stream-buffer-fill-pointer stream)))
628 \f
629 ;;;; user interface to the pretty printer
630
631 (defun pprint-newline (kind &optional stream)
632   #!+sb-doc
633   "Output a conditional newline to STREAM (which defaults to
634    *STANDARD-OUTPUT*) if it is a pretty-printing stream, and do
635    nothing if not. KIND can be one of:
636      :LINEAR - A line break is inserted if and only if the immediatly
637         containing section cannot be printed on one line.
638      :MISER - Same as LINEAR, but only if ``miser-style'' is in effect.
639         (See *PRINT-MISER-WIDTH*.)
640      :FILL - A line break is inserted if and only if either:
641        (a) the following section cannot be printed on the end of the
642            current line,
643        (b) the preceding section was not printed on a single line, or
644        (c) the immediately containing section cannot be printed on one
645            line and miser-style is in effect.
646      :MANDATORY - A line break is always inserted.
647    When a line break is inserted by any type of conditional newline, any
648    blanks that immediately precede the conditional newline are ommitted
649    from the output and indentation is introduced at the beginning of the
650    next line. (See PPRINT-INDENT.)"
651   (declare (type (member :linear :miser :fill :mandatory) kind)
652            (type (or stream (member t nil)) stream)
653            (values null))
654   (let ((stream (case stream
655                   ((t) *terminal-io*)
656                   ((nil) *standard-output*)
657                   (t stream))))
658     (when (pretty-stream-p stream)
659       (enqueue-newline stream kind)))
660   nil)
661
662 (defun pprint-indent (relative-to n &optional stream)
663   #!+sb-doc
664   "Specify the indentation to use in the current logical block if STREAM
665    (which defaults to *STANDARD-OUTPUT*) is it is a pretty-printing stream
666    and do nothing if not. (See PPRINT-LOGICAL-BLOCK.)  N is the indention
667    to use (in ems, the width of an ``m'') and RELATIVE-TO can be either:
668      :BLOCK - Indent relative to the column the current logical block
669         started on.
670      :CURRENT - Indent relative to the current column.
671    The new indention value does not take effect until the following line
672    break."
673   (declare (type (member :block :current) relative-to)
674            (type integer n)
675            (type (or stream (member t nil)) stream)
676            (values null))
677   (let ((stream (case stream
678                   ((t) *terminal-io*)
679                   ((nil) *standard-output*)
680                   (t stream))))
681     (when (pretty-stream-p stream)
682       (enqueue-indent stream relative-to n)))
683   nil)
684
685 (defun pprint-tab (kind colnum colinc &optional stream)
686   #!+sb-doc
687   "If STREAM (which defaults to *STANDARD-OUTPUT*) is a pretty-printing
688    stream, perform tabbing based on KIND, otherwise do nothing. KIND can
689    be one of:
690      :LINE - Tab to column COLNUM. If already past COLNUM tab to the next
691        multiple of COLINC.
692      :SECTION - Same as :LINE, but count from the start of the current
693        section, not the start of the line.
694      :LINE-RELATIVE - Output COLNUM spaces, then tab to the next multiple of
695        COLINC.
696      :SECTION-RELATIVE - Same as :LINE-RELATIVE, but count from the start
697        of the current section, not the start of the line."
698   (declare (type (member :line :section :line-relative :section-relative) kind)
699            (type unsigned-byte colnum colinc)
700            (type (or stream (member t nil)) stream)
701            (values null))
702   (let ((stream (case stream
703                   ((t) *terminal-io*)
704                   ((nil) *standard-output*)
705                   (t stream))))
706     (when (pretty-stream-p stream)
707       (enqueue-tab stream kind colnum colinc)))
708   nil)
709
710 (defun pprint-fill (stream list &optional (colon? t) atsign?)
711   #!+sb-doc
712   "Output LIST to STREAM putting :FILL conditional newlines between each
713    element. If COLON? is NIL (defaults to T), then no parens are printed
714    around the output. ATSIGN? is ignored (but allowed so that PPRINT-FILL
715    can be used with the ~/.../ format directive."
716   (declare (ignore atsign?))
717   (pprint-logical-block (stream list
718                                 :prefix (if colon? "(" "")
719                                 :suffix (if colon? ")" ""))
720     (pprint-exit-if-list-exhausted)
721     (loop
722       (output-object (pprint-pop) stream)
723       (pprint-exit-if-list-exhausted)
724       (write-char #\space stream)
725       (pprint-newline :fill stream))))
726
727 (defun pprint-linear (stream list &optional (colon? t) atsign?)
728   #!+sb-doc
729   "Output LIST to STREAM putting :LINEAR conditional newlines between each
730    element. If COLON? is NIL (defaults to T), then no parens are printed
731    around the output. ATSIGN? is ignored (but allowed so that PPRINT-LINEAR
732    can be used with the ~/.../ format directive."
733   (declare (ignore atsign?))
734   (pprint-logical-block (stream list
735                                 :prefix (if colon? "(" "")
736                                 :suffix (if colon? ")" ""))
737     (pprint-exit-if-list-exhausted)
738     (loop
739       (output-object (pprint-pop) stream)
740       (pprint-exit-if-list-exhausted)
741       (write-char #\space stream)
742       (pprint-newline :linear stream))))
743
744 (defun pprint-tabular (stream list &optional (colon? t) atsign? tabsize)
745   #!+sb-doc
746   "Output LIST to STREAM tabbing to the next column that is an even multiple
747    of TABSIZE (which defaults to 16) between each element. :FILL style
748    conditional newlines are also output between each element. If COLON? is
749    NIL (defaults to T), then no parens are printed around the output.
750    ATSIGN? is ignored (but allowed so that PPRINT-TABULAR can be used with
751    the ~/.../ format directive."
752   (declare (ignore atsign?))
753   (pprint-logical-block (stream list
754                                 :prefix (if colon? "(" "")
755                                 :suffix (if colon? ")" ""))
756     (pprint-exit-if-list-exhausted)
757     (loop
758       (output-object (pprint-pop) stream)
759       (pprint-exit-if-list-exhausted)
760       (write-char #\space stream)
761       (pprint-tab :section-relative 0 (or tabsize 16) stream)
762       (pprint-newline :fill stream))))
763 \f
764 ;;;; pprint-dispatch tables
765
766 (defvar *initial-pprint-dispatch*)
767 (defvar *building-initial-table* nil)
768
769 (defstruct pprint-dispatch-entry
770   ;; The type specifier for this entry.
771   (type (required-argument) :type t)
772   ;; A function to test to see whether an object is of this time. Pretty must
773   ;; just (lambda (obj) (typep object type)) except that we handle the
774   ;; CONS type specially so that (cons (member foo)) works. We don't
775   ;; bother computing this for entries in the CONS hash table, because
776   ;; we don't need it.
777   (test-fn nil :type (or function null))
778   ;; The priority for this guy.
779   (priority 0 :type real)
780   ;; T iff one of the original entries.
781   (initial-p *building-initial-table* :type (member t nil))
782   ;; And the associated function.
783   (function (required-argument) :type function))
784 (def!method print-object ((entry pprint-dispatch-entry) stream)
785   (print-unreadable-object (entry stream :type t)
786     (format stream "type=~S, priority=~S~@[ [initial]~]"
787             (pprint-dispatch-entry-type entry)
788             (pprint-dispatch-entry-priority entry)
789             (pprint-dispatch-entry-initial-p entry))))
790
791 (defstruct pprint-dispatch-table
792   ;; A list of all the entries (except for CONS entries below) in highest
793   ;; to lowest priority.
794   (entries nil :type list)
795   ;; A hash table mapping things to entries for type specifiers of the
796   ;; form (CONS (MEMBER <thing>)). If the type specifier is of this form,
797   ;; we put it in this hash table instead of the regular entries table.
798   (cons-entries (make-hash-table :test 'eql)))
799 (def!method print-object ((table pprint-dispatch-table) stream)
800   (print-unreadable-object (table stream :type t :identity t)))
801
802 (defun cons-type-specifier-p (spec)
803   (and (consp spec)
804        (eq (car spec) 'cons)
805        (cdr spec)
806        (null (cddr spec))
807        (let ((car (cadr spec)))
808          (and (consp car)
809               (let ((carcar (car car)))
810                 (or (eq carcar 'member)
811                     (eq carcar 'eql)))
812               (cdr car)
813               (null (cddr car))))))
814
815 (defun entry< (e1 e2)
816   (declare (type pprint-dispatch-entry e1 e2))
817   (if (pprint-dispatch-entry-initial-p e1)
818       (if (pprint-dispatch-entry-initial-p e2)
819           (< (pprint-dispatch-entry-priority e1)
820              (pprint-dispatch-entry-priority e2))
821           t)
822       (if (pprint-dispatch-entry-initial-p e2)
823           nil
824           (< (pprint-dispatch-entry-priority e1)
825              (pprint-dispatch-entry-priority e2)))))
826
827 (macrolet ((frob (x)
828              `(cons ',x #'(lambda (object) ,x))))
829   (defvar *precompiled-pprint-dispatch-funs*
830     (list (frob (typep object 'array))
831           (frob (and (consp object)
832                      (and (typep (car object) 'symbol)
833                           (typep (car object) '(satisfies fboundp)))))
834           (frob (typep object 'cons)))))
835
836 (defun compute-test-fn (type)
837   (let ((was-cons nil))
838     (labels ((compute-test-expr (type object)
839                (if (listp type)
840                    (case (car type)
841                      (cons
842                       (setq was-cons t)
843                       (destructuring-bind
844                           (&optional (car nil car-p) (cdr nil cdr-p))
845                           (cdr type)
846                         `(and (consp ,object)
847                               ,@(when car-p
848                                   `(,(compute-test-expr
849                                       car `(car ,object))))
850                               ,@(when cdr-p
851                                   `(,(compute-test-expr
852                                       cdr `(cdr ,object)))))))
853                      (not
854                       (destructuring-bind (type) (cdr type)
855                         `(not ,(compute-test-expr type object))))
856                      (and
857                       `(and ,@(mapcar #'(lambda (type)
858                                           (compute-test-expr type object))
859                                       (cdr type))))
860                      (or
861                       `(or ,@(mapcar #'(lambda (type)
862                                          (compute-test-expr type object))
863                                      (cdr type))))
864                      (t
865                       `(typep ,object ',type)))
866                    `(typep ,object ',type))))
867       (let ((expr (compute-test-expr type 'object)))
868         (cond ((cdr (assoc expr *precompiled-pprint-dispatch-funs*
869                            :test #'equal)))
870               ((fboundp 'compile)
871                (compile nil `(lambda (object) ,expr)))
872               (was-cons
873                (warn "CONS PPRINT dispatch ignored w/o compiler loaded:~%  ~S"
874                      type)
875                #'(lambda (object) (declare (ignore object)) nil))
876               (t
877                (let ((ttype (sb!kernel:specifier-type type)))
878                  #'(lambda (object) (sb!kernel:%typep object ttype)))))))))
879
880 (defun copy-pprint-dispatch (&optional (table *print-pprint-dispatch*))
881   (declare (type (or pprint-dispatch-table null) table))
882   (let* ((orig (or table *initial-pprint-dispatch*))
883          (new (make-pprint-dispatch-table
884                :entries (copy-list (pprint-dispatch-table-entries orig))))
885          (new-cons-entries (pprint-dispatch-table-cons-entries new)))
886     (maphash #'(lambda (key value)
887                  (setf (gethash key new-cons-entries) value))
888              (pprint-dispatch-table-cons-entries orig))
889     new))
890
891 (defun pprint-dispatch (object &optional (table *print-pprint-dispatch*))
892   (declare (type (or pprint-dispatch-table null) table))
893   (let* ((table (or table *initial-pprint-dispatch*))
894          (cons-entry
895           (and (consp object)
896                (gethash (car object)
897                         (pprint-dispatch-table-cons-entries table))))
898          (entry
899           (dolist (entry (pprint-dispatch-table-entries table) cons-entry)
900             (when (and cons-entry
901                        (entry< entry cons-entry))
902               (return cons-entry))
903             (when (funcall (pprint-dispatch-entry-test-fn entry) object)
904               (return entry)))))
905     (if entry
906         (values (pprint-dispatch-entry-function entry) t)
907         (values #'(lambda (stream object)
908                     (output-ugly-object object stream))
909                 nil))))
910
911 (defun set-pprint-dispatch (type function &optional
912                             (priority 0) (table *print-pprint-dispatch*))
913   (declare (type (or null function) function)
914            (type real priority)
915            (type pprint-dispatch-table table))
916   (if function
917       (if (cons-type-specifier-p type)
918           (setf (gethash (second (second type))
919                          (pprint-dispatch-table-cons-entries table))
920                 (make-pprint-dispatch-entry :type type :priority priority
921                                             :function function))
922           (let ((list (delete type (pprint-dispatch-table-entries table)
923                               :key #'pprint-dispatch-entry-type
924                               :test #'equal))
925                 (entry (make-pprint-dispatch-entry
926                         :type type :test-fn (compute-test-fn type)
927                         :priority priority :function function)))
928             (do ((prev nil next)
929                  (next list (cdr next)))
930                 ((null next)
931                  (if prev
932                      (setf (cdr prev) (list entry))
933                      (setf list (list entry))))
934               (when (entry< (car next) entry)
935                 (if prev
936                     (setf (cdr prev) (cons entry next))
937                     (setf list (cons entry next)))
938                 (return)))
939             (setf (pprint-dispatch-table-entries table) list)))
940       (if (cons-type-specifier-p type)
941           (remhash (second (second type))
942                    (pprint-dispatch-table-cons-entries table))
943           (setf (pprint-dispatch-table-entries table)
944                 (delete type (pprint-dispatch-table-entries table)
945                         :key #'pprint-dispatch-entry-type
946                         :test #'equal))))
947   nil)
948 \f
949 ;;;; standard pretty-printing routines
950
951 (defun pprint-array (stream array)
952   (cond ((or (and (null *print-array*) (null *print-readably*))
953              (stringp array)
954              (bit-vector-p array))
955          (output-ugly-object array stream))
956         ((and *print-readably* (not (eq (array-element-type array) 't)))
957          (let ((*print-readably* nil))
958            (error 'print-not-readable :object array)))
959         ((vectorp array)
960          (pprint-vector stream array))
961         (t
962          (pprint-multi-dim-array stream array))))
963
964 (defun pprint-vector (stream vector)
965   (pprint-logical-block (stream nil :prefix "#(" :suffix ")")
966     (dotimes (i (length vector))
967       (unless (zerop i)
968         (format stream " ~:_"))
969       (pprint-pop)
970       (output-object (aref vector i) stream))))
971
972 (defun pprint-multi-dim-array (stream array)
973   (funcall (formatter "#~DA") stream (array-rank array))
974   (with-array-data ((data array) (start) (end))
975     (declare (ignore end))
976     (labels ((output-guts (stream index dimensions)
977                (if (null dimensions)
978                    (output-object (aref data index) stream)
979                    (pprint-logical-block
980                        (stream nil :prefix "(" :suffix ")")
981                      (let ((dim (car dimensions)))
982                        (unless (zerop dim)
983                          (let* ((dims (cdr dimensions))
984                                 (index index)
985                                 (step (reduce #'* dims))
986                                 (count 0))
987                            (loop                                
988                              (pprint-pop)
989                              (output-guts stream index dims)
990                              (when (= (incf count) dim)
991                                (return))
992                              (write-char #\space stream)
993                              (pprint-newline (if dims :linear :fill)
994                                              stream)
995                              (incf index step)))))))))
996       (output-guts stream start (array-dimensions array)))))
997
998 (defun pprint-lambda-list (stream lambda-list &rest noise)
999   (declare (ignore noise))
1000   (pprint-logical-block (stream lambda-list :prefix "(" :suffix ")")
1001     (let ((state :required)
1002           (first t))
1003       (loop
1004         (pprint-exit-if-list-exhausted)
1005         (unless first
1006           (write-char #\space stream))
1007         (let ((arg (pprint-pop)))
1008           (unless first
1009             (case arg
1010               (&optional
1011                (setf state :optional)
1012                (pprint-newline :linear stream))
1013               ((&rest &body)
1014                (setf state :required)
1015                (pprint-newline :linear stream))
1016               (&key
1017                (setf state :key)
1018                (pprint-newline :linear stream))
1019               (&aux
1020                (setf state :optional)
1021                (pprint-newline :linear stream))
1022               (t
1023                (pprint-newline :fill stream))))
1024           (ecase state
1025             (:required
1026              (pprint-lambda-list stream arg))
1027             ((:optional :key)
1028              (pprint-logical-block
1029                  (stream arg :prefix "(" :suffix ")")
1030                (pprint-exit-if-list-exhausted)
1031                (if (eq state :key)
1032                    (pprint-logical-block
1033                        (stream (pprint-pop) :prefix "(" :suffix ")")
1034                      (pprint-exit-if-list-exhausted)
1035                      (output-object (pprint-pop) stream)
1036                      (pprint-exit-if-list-exhausted)
1037                      (write-char #\space stream)
1038                      (pprint-newline :fill stream)
1039                      (pprint-lambda-list stream (pprint-pop))
1040                      (loop
1041                        (pprint-exit-if-list-exhausted)
1042                        (write-char #\space stream)
1043                        (pprint-newline :fill stream)
1044                        (output-object (pprint-pop) stream)))
1045                    (pprint-lambda-list stream (pprint-pop)))
1046                (loop
1047                  (pprint-exit-if-list-exhausted)
1048                  (write-char #\space stream)
1049                  (pprint-newline :linear stream)
1050                  (output-object (pprint-pop) stream))))))
1051         (setf first nil)))))
1052
1053 (defun pprint-lambda (stream list &rest noise)
1054   (declare (ignore noise))
1055   (funcall (formatter
1056             ;; KLUDGE: This format string, and other format strings which also
1057             ;; refer to SB!PRETTY, rely on the current SBCL not-quite-ANSI
1058             ;; behavior of FORMATTER in order to make code which survives the
1059             ;; transition when SB!PRETTY is renamed to SB-PRETTY after cold
1060             ;; init. (ANSI says that the FORMATTER functions should be
1061             ;; equivalent to the format string, but the SBCL FORMATTER
1062             ;; functions contain references to package objects, not package
1063             ;; names, so they keep right on going if the packages are renamed.)
1064             ;; If our FORMATTER behavior is ever made more compliant, the code
1065             ;; here will have to change. -- WHN 19991207
1066             "~:<~^~W~^~3I ~:_~/SB!PRETTY:PPRINT-LAMBDA-LIST/~1I~@{ ~_~W~}~:>")
1067            stream
1068            list))
1069
1070 (defun pprint-block (stream list &rest noise)
1071   (declare (ignore noise))
1072   (funcall (formatter "~:<~^~W~^~3I ~:_~W~1I~@{ ~_~W~}~:>") stream list))
1073
1074 (defun pprint-flet (stream list &rest noise)
1075   (declare (ignore noise))
1076   (funcall (formatter
1077             "~:<~^~W~^ ~@_~:<~@{~:<~^~W~^~3I ~:_~/SB!PRETTY:PPRINT-LAMBDA-LIST/~1I~:@_~@{~W~^ ~_~}~:>~^ ~_~}~:>~1I~@:_~@{~W~^ ~_~}~:>")
1078            stream
1079            list))
1080
1081 (defun pprint-let (stream list &rest noise)
1082   (declare (ignore noise))
1083   (funcall (formatter "~:<~^~W~^ ~@_~:<~@{~:<~^~W~@{ ~_~W~}~:>~^ ~_~}~:>~1I~:@_~@{~W~^ ~_~}~:>")
1084            stream
1085            list))
1086
1087 (defun pprint-progn (stream list &rest noise)
1088   (declare (ignore noise))
1089   (funcall (formatter "~:<~^~W~@{ ~_~W~}~:>") stream list))
1090
1091 (defun pprint-progv (stream list &rest noise)
1092   (declare (ignore noise))
1093   (funcall (formatter "~:<~^~W~^~3I ~_~W~^ ~_~W~^~1I~@{ ~_~W~}~:>")
1094            stream list))
1095
1096 (defun pprint-quote (stream list &rest noise)
1097   (declare (ignore noise))
1098   (if (and (consp list)
1099            (consp (cdr list))
1100            (null (cddr list)))
1101       (case (car list)
1102         (function
1103          (write-string "#'" stream)
1104          (output-object (cadr list) stream))
1105         (quote
1106          (write-char #\' stream)
1107          (output-object (cadr list) stream))
1108         (t
1109          (pprint-fill stream list)))
1110       (pprint-fill stream list)))
1111
1112 (defun pprint-setq (stream list &rest noise)
1113   (declare (ignore noise))
1114   (pprint-logical-block (stream list :prefix "(" :suffix ")")
1115     (pprint-exit-if-list-exhausted)
1116     (output-object (pprint-pop) stream)
1117     (pprint-exit-if-list-exhausted)
1118     (write-char #\space stream)
1119     (pprint-newline :miser stream)
1120     (if (and (consp (cdr list)) (consp (cddr list)))
1121         (loop
1122           (pprint-indent :current 2 stream)
1123           (output-object (pprint-pop) stream)
1124           (pprint-exit-if-list-exhausted)
1125           (write-char #\space stream)
1126           (pprint-newline :linear stream)
1127           (pprint-indent :current -2 stream)
1128           (output-object (pprint-pop) stream)
1129           (pprint-exit-if-list-exhausted)
1130           (write-char #\space stream)
1131           (pprint-newline :linear stream))
1132         (progn
1133           (pprint-indent :current 0 stream)
1134           (output-object (pprint-pop) stream)
1135           (pprint-exit-if-list-exhausted)
1136           (write-char #\space stream)
1137           (pprint-newline :linear stream)
1138           (output-object (pprint-pop) stream)))))
1139
1140 ;;; FIXME: could become SB!XC:DEFMACRO wrapped in EVAL-WHEN (COMPILE EVAL)
1141 (defmacro pprint-tagbody-guts (stream)
1142   `(loop
1143      (pprint-exit-if-list-exhausted)
1144      (write-char #\space ,stream)
1145      (let ((form-or-tag (pprint-pop)))
1146        (pprint-indent :block
1147                       (if (atom form-or-tag) 0 1)
1148                       ,stream)
1149        (pprint-newline :linear ,stream)
1150        (output-object form-or-tag ,stream))))
1151
1152 (defun pprint-tagbody (stream list &rest noise)
1153   (declare (ignore noise))
1154   (pprint-logical-block (stream list :prefix "(" :suffix ")")
1155     (pprint-exit-if-list-exhausted)
1156     (output-object (pprint-pop) stream)
1157     (pprint-tagbody-guts stream)))
1158
1159 (defun pprint-case (stream list &rest noise)
1160   (declare (ignore noise))
1161   (funcall (formatter
1162             "~:<~^~W~^ ~3I~:_~W~1I~@{ ~_~:<~^~:/SB!PRETTY:PPRINT-FILL/~^~@{ ~_~W~}~:>~}~:>")
1163            stream
1164            list))
1165
1166 (defun pprint-defun (stream list &rest noise)
1167   (declare (ignore noise))
1168   (funcall (formatter
1169             "~:<~^~W~^ ~@_~:I~W~^ ~:_~/SB!PRETTY:PPRINT-LAMBDA-LIST/~1I~@{ ~_~W~}~:>")
1170            stream
1171            list))
1172
1173 (defun pprint-destructuring-bind (stream list &rest noise)
1174   (declare (ignore noise))
1175   (funcall (formatter
1176             "~:<~^~W~^~3I ~_~:/SB!PRETTY:PPRINT-LAMBDA-LIST/~^ ~_~W~^~1I~@{ ~_~W~}~:>")
1177            stream list))
1178
1179 (defun pprint-do (stream list &rest noise)
1180   (declare (ignore noise))
1181   (pprint-logical-block (stream list :prefix "(" :suffix ")")
1182     (pprint-exit-if-list-exhausted)
1183     (output-object (pprint-pop) stream)
1184     (pprint-exit-if-list-exhausted)
1185     (write-char #\space stream)
1186     (pprint-indent :current 0 stream)
1187     (funcall (formatter "~:<~@{~:<~^~W~^ ~@_~:I~W~@{ ~_~W~}~:>~^~:@_~}~:>")
1188              stream
1189              (pprint-pop))
1190     (pprint-exit-if-list-exhausted)
1191     (write-char #\space stream)
1192     (pprint-newline :linear stream)
1193     (pprint-linear stream (pprint-pop))
1194     (pprint-tagbody-guts stream)))
1195
1196 (defun pprint-dolist (stream list &rest noise)
1197   (declare (ignore noise))
1198   (pprint-logical-block (stream list :prefix "(" :suffix ")")
1199     (pprint-exit-if-list-exhausted)
1200     (output-object (pprint-pop) stream)
1201     (pprint-exit-if-list-exhausted)
1202     (pprint-indent :block 3 stream)
1203     (write-char #\space stream)
1204     (pprint-newline :fill stream)
1205     (funcall (formatter "~:<~^~W~^ ~:_~:I~W~@{ ~_~W~}~:>")
1206              stream
1207              (pprint-pop))
1208     (pprint-tagbody-guts stream)))
1209
1210 (defun pprint-typecase (stream list &rest noise)
1211   (declare (ignore noise))
1212   (funcall (formatter
1213             "~:<~^~W~^ ~3I~:_~W~1I~@{ ~_~:<~^~W~^~@{ ~_~W~}~:>~}~:>")
1214            stream
1215            list))
1216
1217 (defun pprint-prog (stream list &rest noise)
1218   (declare (ignore noise))
1219   (pprint-logical-block (stream list :prefix "(" :suffix ")")
1220     (pprint-exit-if-list-exhausted)
1221     (output-object (pprint-pop) stream)
1222     (pprint-exit-if-list-exhausted)
1223     (write-char #\space stream)
1224     (pprint-newline :miser stream)
1225     (pprint-fill stream (pprint-pop))
1226     (pprint-tagbody-guts stream)))
1227
1228 (defun pprint-function-call (stream list &rest noise)
1229   (declare (ignore noise))
1230   (funcall (formatter "~:<~^~W~^ ~:_~:I~@{~W~^ ~_~}~:>")
1231            stream
1232            list))
1233 \f
1234 ;;;; the interface seen by regular (ugly) printer and initialization routines
1235
1236 ;;; OUTPUT-PRETTY-OBJECT is called by OUTPUT-OBJECT when *PRINT-PRETTY* is
1237 ;;; bound to T.
1238 (defun output-pretty-object (object stream)
1239   (with-pretty-stream (stream)
1240     (funcall (pprint-dispatch object) stream object)))
1241
1242 (defun !pprint-cold-init ()
1243   (/show0 "entering !PPRINT-COLD-INIT")
1244   (setf *initial-pprint-dispatch* (make-pprint-dispatch-table))
1245   (let ((*print-pprint-dispatch* *initial-pprint-dispatch*)
1246         (*building-initial-table* t))
1247     ;; printers for regular types
1248     (/show0 "doing SET-PPRINT-DISPATCH for regular types")
1249     (set-pprint-dispatch 'array #'pprint-array)
1250     (set-pprint-dispatch '(cons (and symbol (satisfies fboundp)))
1251                          #'pprint-function-call -1)
1252     (set-pprint-dispatch 'cons #'pprint-fill -2)
1253     ;; cons cells with interesting things for the car
1254     (/show0 "doing SET-PPRINT-DISPATCH for CONS with interesting CAR")
1255
1256     (dolist (magic-form '((lambda pprint-lambda)
1257
1258                           ;; special forms
1259                           (block pprint-block)
1260                           (catch pprint-block)
1261                           (eval-when pprint-block)
1262                           (flet pprint-flet)
1263                           (function pprint-quote)
1264                           (labels pprint-flet)
1265                           (let pprint-let)
1266                           (let* pprint-let)
1267                           (locally pprint-progn)
1268                           (macrolet pprint-flet)
1269                           (multiple-value-call pprint-block)
1270                           (multiple-value-prog1 pprint-block)
1271                           (progn pprint-progn)
1272                           (progv pprint-progv)
1273                           (quote pprint-quote)
1274                           (return-from pprint-block)
1275                           (setq pprint-setq)
1276                           (symbol-macrolet pprint-let)
1277                           (tagbody pprint-tagbody)
1278                           (throw pprint-block)
1279                           (unwind-protect pprint-block)
1280
1281                           ;; macros
1282                           (case pprint-case)
1283                           (ccase pprint-case)
1284                           (ctypecase pprint-typecase)
1285                           (defconstant pprint-block)
1286                           (define-modify-macro pprint-defun)
1287                           (define-setf-expander pprint-defun)
1288                           (defmacro pprint-defun)
1289                           (defparameter pprint-block)
1290                           (defsetf pprint-defun)
1291                           (defstruct pprint-block)
1292                           (deftype pprint-defun)
1293                           (defun pprint-defun)
1294                           (defvar pprint-block)
1295                           (destructuring-bind pprint-destructuring-bind)
1296                           (do pprint-do)
1297                           (do* pprint-do)
1298                           (do-all-symbols pprint-dolist)
1299                           (do-external-symbols pprint-dolist)
1300                           (do-symbols pprint-dolist)
1301                           (dolist pprint-dolist)
1302                           (dotimes pprint-dolist)
1303                           (ecase pprint-case)
1304                           (etypecase pprint-typecase)
1305                           #+nil (handler-bind ...)
1306                           #+nil (handler-case ...)
1307                           #+nil (loop ...)
1308                           (multiple-value-bind pprint-progv)
1309                           (multiple-value-setq pprint-block)
1310                           (pprint-logical-block pprint-block)
1311                           (print-unreadable-object pprint-block)
1312                           (prog pprint-prog)
1313                           (prog* pprint-prog)
1314                           (prog1 pprint-block)
1315                           (prog2 pprint-progv)
1316                           (psetf pprint-setq)
1317                           (psetq pprint-setq)
1318                           #+nil (restart-bind ...)
1319                           #+nil (restart-case ...)
1320                           (setf pprint-setq)
1321                           (step pprint-progn)
1322                           (time pprint-progn)
1323                           (typecase pprint-typecase)
1324                           (unless pprint-block)
1325                           (when pprint-block)
1326                           (with-compilation-unit pprint-block)
1327                           #+nil (with-condition-restarts ...)
1328                           (with-hash-table-iterator pprint-block)
1329                           (with-input-from-string pprint-block)
1330                           (with-open-file pprint-block)
1331                           (with-open-stream pprint-block)
1332                           (with-output-to-string pprint-block)
1333                           (with-package-iterator pprint-block)
1334                           (with-simple-restart pprint-block)
1335                           (with-standard-io-syntax pprint-progn)))
1336
1337       (set-pprint-dispatch `(cons (eql ,(first magic-form)))
1338                            (symbol-function (second magic-form))))
1339
1340     ;; other pretty-print init forms
1341     (/show0 "about to call !BACKQ-PP-COLD-INIT")
1342     (sb!impl::!backq-pp-cold-init)
1343     (/show0 "leaving !PPRINT-COLD-INIT"))
1344
1345   (setf *print-pprint-dispatch* (copy-pprint-dispatch nil))
1346   (setf *pretty-printer* #'output-pretty-object)
1347   (setf *print-pretty* t))