Forked from
cmucl / cmucl
10161 commits behind the upstream repository.
print.lisp 57.29 KiB
;;; -*- Log: code.log; Package: Lisp -*-
;;;
;;; **********************************************************************
;;; This code was written as part of the CMU Common Lisp project at
;;; Carnegie Mellon University, and has been placed in the public domain.
;;; If you want to use this code or any part of CMU Common Lisp, please contact
;;; Scott Fahlman or slisp-group@cs.cmu.edu.
;;;
(ext:file-comment
"$Header: /Volumes/share2/src/cmucl/cvs2git/cvsroot/src/code/print.lisp,v 1.32 1992/01/02 23:44:17 ram Exp $")
;;;
;;; **********************************************************************
;;;
;;; CMU Common Lisp printer.
;;;
;;; Written by Neal Feinberg, Bill Maddox, Steven Handerson, and Skef Wholey.
;;; Modified by various CMU Common Lisp maintainers.
;;;
(in-package "LISP")
(export '(*print-readably* *print-escape* *print-pretty* *print-circle*
*print-base* *print-radix* *print-case* *print-gensym* *print-level*
*print-length* *print-array* *print-lines* *print-right-margin*
*print-miser-width* *print-pprint-dispatch* with-standard-io-syntax
write prin1 print princ pprint
write-to-string prin1-to-string princ-to-string
print-unreadable-object))
(in-package "KERNEL")
(export '(*current-level* *pretty-printer* output-object output-ugly-object
check-for-circularity handle-circularity with-circularity-detection
descend-into punt-if-too-long))
(in-package "LISP")
;;;; Exported printer control variables.
(defvar *print-readably* nil
"If true, all objects will printed readably. If readably printing is
impossible, an error will be signalled. This overrides the value of
*PRINT-ESCAPE*.")
(defvar *print-escape* T
"Flag which indicates that slashification is on. See the manual")
(defvar *print-pretty* nil
"Flag which indicates that pretty printing is to be used")
(defvar *print-base* 10.
"The output base for integers and rationals.")
(defvar *print-radix* nil
"This flag requests to verify base when printing rationals.")
(defvar *print-level* nil
"How many levels deep to print. Unlimited if null.")
(defvar *print-length* nil
"How many elements to print on each level. Unlimited if null.")
(defvar *print-circle* nil
"Whether to worry about circular list structures. See the manual.")
(defvar *print-case* :upcase
"What kind of case the printer should use by default")
(defvar *print-array* t
"Whether the array should print it's guts out")
(defvar *print-gensym* t
"If true, symbols with no home package are printed with a #: prefix.
If false, no prefix is printed.")
(defvar *print-lines* nil
"The maximum number of lines to print. If NIL, unlimited.")
(defvar *print-right-margin* nil
"The position of the right margin in ems. If NIL, try to determine this
from the stream in use.")
(defvar *print-miser-width* nil
"If the remaining space between the current column and the right margin
is less than this, then print using ``miser-style'' output. Miser
style conditional newlines are turned on, and all indentations are
turned off. If NIL, never use miser mode.")
(defvar *print-pprint-dispatch* nil
"The pprint-dispatch-table that controls how to pretty print objects. See
COPY-PPRINT-DISPATH, PPRINT-DISPATCH, and SET-PPRINT-DISPATCH.")
(defmacro with-standard-io-syntax (&body body)
"Bind the reader and printer control variables to values that enable READ
to reliably read the results of PRINT. These values are:
*PACKAGE* The COMMON-LISP-USER package
*PRINT-ARRAY* T
*PRINT-BASE* 10
*PRINT-CASE* :UPCASE
*PRINT-CIRCLE* NIL
*PRINT-ESCAPE* T
*PRINT-GENSYM* T
*PRINT-LENGTH* NIL
*PRINT-LEVEL* NIL
*PRINT-LINES* NIL
*PRINT-MISER-WIDTH* NIL
*PRINT-PRETTY* NIL
*PRINT-RADIX* NIL
*PRINT-READABLY* T
*PRINT-RIGHT-MARGIN* NIL
*READ-BASE* 10
*READ-DEFAULT-FLOAT-FORMAT* SINGLE-FLOAT
*READ-EVAL* T
*READ-SUPPRESS* NIL
*READTABLE* the standard readtable."
`(%with-standard-io-syntax #'(lambda () ,@body)))
(defun %with-standard-io-syntax (function)
(let ((*package* (find-package "USER"))
(*print-array* t)
(*print-base* 10)
(*print-case* :upcase)
(*print-circle* nil)
(*print-escape* t)
(*print-gensym* t)
(*print-length* nil)
(*print-level* nil)
(*print-lines* nil)
(*print-miser-width* nil)
(*print-pretty* nil)
(*print-radix* nil)
(*print-readably* t)
(*print-right-margin* nil)
(*read-base* 10)
(*read-default-float-format* 'single-float)
(*read-eval* t)
(*read-suppress* nil)
(*readtable* std-lisp-readtable))
(funcall function)))
;;;; Routines to print objects.
(defun write (object &key
((:stream stream) *standard-output*)
((:escape *print-escape*) *print-escape*)
((:radix *print-radix*) *print-radix*)
((:base *print-base*) *print-base*)
((:circle *print-circle*) *print-circle*)
((:pretty *print-pretty*) *print-pretty*)
((:level *print-level*) *print-level*)
((:length *print-length*) *print-length*)
((:case *print-case*) *print-case*)
((:array *print-array*) *print-array*)
((:gensym *print-gensym*) *print-gensym*)
((:readably *print-readably*) *print-readably*)
((:right-margin *print-right-margin*)
*print-right-margin*)
((:miser-width *print-miser-width*)
*print-miser-width*)
((:lines *print-lines*) *print-lines*)
((:pprint-dispatch *print-pprint-dispatch*)
*print-pprint-dispatch*))
"Outputs OBJECT to the specified stream, defaulting to *standard-output*"
(output-object object (out-synonym-of stream))
object)
(defun prin1 (object &optional stream)
"Outputs a mostly READable printed representation of OBJECT on the specified
stream."
(let ((*print-escape* T))
(output-object object (out-synonym-of stream)))
object)
(defun princ (object &optional stream)
"Outputs an asthetic but not READable printed representation of OBJECT on the
specified stream."
(let ((*print-escape* NIL))
(output-object object (out-synonym-of stream)))
object)
(defun print (object &optional stream)
"Outputs a terpri, the mostly READable printed represenation of OBJECT, and
space to the stream."
(let ((stream (out-synonym-of stream)))
(terpri stream)
(prin1 object stream)
(write-char #\space stream)
object))
(defun pprint (object &optional stream)
"Prettily outputs the Object preceded by a newline."
(let ((*print-pretty* t)
(*print-escape* t))
(terpri stream)
(output-object object stream))
(values))
(defun write-to-string
(object &key
((:escape *print-escape*) *print-escape*)
((:radix *print-radix*) *print-radix*)
((:base *print-base*) *print-base*)
((:circle *print-circle*) *print-circle*)
((:pretty *print-pretty*) *print-pretty*)
((:level *print-level*) *print-level*)
((:length *print-length*) *print-length*)
((:case *print-case*) *print-case*)
((:array *print-array*) *print-array*)
((:gensym *print-gensym*) *print-gensym*)
((:readably *print-readably*) *print-readably*)
((:right-margin *print-right-margin*) *print-right-margin*)
((:miser-width *print-miser-width*) *print-miser-width*)
((:lines *print-lines*) *print-lines*)
((:pprint-dispatch *print-pprint-dispatch*)
*print-pprint-dispatch*))
"Returns the printed representation of OBJECT as a string."
(stringify-object object))
(defun prin1-to-string (object)
"Returns the printed representation of OBJECT as a string with
slashification on."
(stringify-object object t))
(defun princ-to-string (object)
"Returns the printed representation of OBJECT as a string with
slashification off."
(stringify-object object nil))
;;; STRINGIFY-OBJECT -- Internal.
;;;
;;; This produces the printed representation of an object as a string. The
;;; few ...-TO-STRING functions above call this.
;;;
(defvar *string-output-streams* ())
;;;
(defun stringify-object (object &optional (*print-escape* *print-escape*))
(let ((stream (if *string-output-streams*
(pop *string-output-streams*)
(make-string-output-stream))))
(setup-printer-state)
(output-object object stream)
(prog1
(get-output-stream-string stream)
(push stream *string-output-streams*))))
;;;; PRINT-UNREADABLE-OBJECT macro
(defmacro print-unreadable-object ((object stream &key type identity)
&body body)
`(%print-unreadable-object ,object ,stream ,type ,identity
,(if body
`#'(lambda () ,@body)
nil)))
(defun %print-unreadable-object (object stream type identity body)
(when *print-readably*
(error "~S cannot be printed readably." object))
(write-string "#<" stream)
(when type
(write (type-of object) :stream stream :circle nil
:level nil :length nil)
(when (or body identity)
(write-char #\space stream)))
(when body
(funcall body))
(when identity
(when body
(write-char #\space stream))
(write-char #\{ stream)
(write (get-lisp-obj-address object) :stream stream
:radix nil :base 16)
(write-char #\} stream))
(write-char #\> stream))
;;;; WHITESPACE-CHAR-P
;;; This is used in other files, but is defined in this one for some reason.
(defun whitespace-char-p (char)
"Determines whether or not the character is considered whitespace."
(or (char= char #\space)
(char= char #\tab)
(char= char #\return)
(char= char #\linefeed)))
;;;; Circularity detection stuff.
;;; *CURRENT-STRUCTURE* -- internal
;;;
;;; We have to bend over backwards in order to make sure depth abbrevs and
;;; circularity detection work right despite the fact that the user supplied
;;; print function may or may not do anything special.
;;;
;;; In order to correctly handle depth abbrevs, OUTPUT-STRUCTURE binds a
;;; this to the structure being output. If the descend-into stuff notices
;;; that we are trying to descend into that structure, we don't bother
;;; doing the depth check/inc because we know it's already been done. But
;;; if we try to descend into something else, then we know that the
;;; structure printer is being stupid and didn't check the depth or for
;;; circularities.
;;;
(defvar *current-structure* nil)
;;; *CIRCULARITY-HASH-TABLE* -- internal.
;;;
;;; When *print-circle* is T, this gets bound to a hash table that (eventually)
;;; ends up with entries for every object printed. When we are initially
;;; looking for circularities, we enter a T when we find an object for the
;;; first time, and a 0 when we encounter an object a second time around.
;;; When we are actually printing, the 0 entries get changed to the actual
;;; marker value when they are first printed.
;;;
(defvar *circularity-hash-table* nil)
;;; *CIRCULARITY-COUNTER* -- internal.
;;;
;;; When NIL, we are just looking for circularities. After we have found them
;;; all, this gets bound to 0. Then whenever we need a new marker, it is
;;; incremented.
;;;
(defvar *circularity-counter* nil)
;;; CHECK-FOR-CIRCULARITY -- interface.
;;;
(defun check-for-circularity (object &optional assign)
"Check to see if OBJECT is a circular reference, and return something non-NIL
if it is. If ASSIGN is T, then the number to use in the #n= and #n# noise
is assigned at this time. Note: CHECK-FOR-CIRCULARITY must be called
*EXACTLY* once with ASSIGN T, or the circularity detection noise will get
confused about when to use #n= and when to use #n#. If this returns
non-NIL when ASSIGN is T, then you must call HANDLE-CIRCULARITY on it.
If you are not using this inside a WITH-CIRCULARITY-DETECTION, then you
have to be prepared to handle a return value of :INITIATE which means it
needs to initiate the circularity detection noise. See the source for
info on how to do that."
(cond ((null *print-circle*)
;; Don't bother, nobody cares.
nil)
((eq object *current-structure*)
;; It's already been handled by output-structure.
nil)
((null *circularity-hash-table*)
:initiate)
((null *circularity-counter*)
(ecase (gethash object *circularity-hash-table*)
((nil)
;; First encounter.
(setf (gethash object *circularity-hash-table*) t)
;; We need to keep looking.
nil)
((t)
;; Second encounter.
(setf (gethash object *circularity-hash-table*) 0)
;; It's a circular reference.
t)
(0
;; It's a circular reference.
t)))
(t
(let ((value (gethash object *circularity-hash-table*)))
(case value
((nil)
;; We found an object that wasn't there the first time around.
(let ((*print-circle* nil))
(error "Found an object on the second pass that wasn't there ~
on the first pass.")))
((t)
;; Exactly one occurance of this object appears. That's good.
nil)
(0
(if assign
(let ((value (incf *circularity-counter*)))
;; First occurance of this object. Set the counter.
(setf (gethash object *circularity-hash-table*) value)
value)
t))
(t
;; Second or later occurance.
(- value)))))))
;;; HANDLE-CIRCULARITY -- interface.
;;;
(defun handle-circularity (marker stream)
"Handle the results of CHECK-FOR-CIRCULARITY. If this returns T then
you should go ahead and print the object. If it returns NIL, then
you should blow it off."
(case marker
(:initiate
;; Someone forgor to initiate circularity detection.
(let ((*print-circle* nil))
(error "Attempt to use CHECK-FOR-CIRCULARITY when circularity ~
checking has not been initiated.")))
((t)
;; It's a second (or later) reference to the object while we are
;; just looking. So don't bother groveling it again.
nil)
(t
(write-char #\# stream)
(let ((*print-base* 10) (*print-radix* nil))
(cond ((minusp marker)
(output-integer (- marker) stream)
(write-char #\# stream)
nil)
(t
(output-integer marker stream)
(write-char #\= stream)
t))))))
;;; WITH-CIRCULARITY-DETECTION -- interface.
;;;
(defmacro with-circularity-detection ((object stream) &body body)
"Check to see if OBJECT needs to be delt with specially, and if so, do
whatever is necessary. STREAM is the stream that the object is being
printed to (so we know where to print the #n= and #n#). Note: BODY
might be executed twice, so it cannot have any side effects. Also,
while initially looking for circularities, STREAM is rebound to a
stream that ignores all output so it must be a bindable symbol."
(let ((user-body (gensym))
(checker (gensym)))
(once-only ((object object))
`(labels ((,user-body (,stream)
(let ((*current-structure* nil))
,@body))
(,checker (,stream)
(let ((marker (check-for-circularity ,object t)))
(case marker
(:initiate
(let ((*circularity-hash-table*
(make-hash-table :test #'eq)))
(,checker (make-broadcast-stream))
(let ((*circularity-counter* 0))
(,checker ,stream))))
((nil)
(,user-body ,stream))
(t
(when (handle-circularity marker ,stream)
(,user-body ,stream)))))))
(,checker ,stream)))))
;;;; Level and Length abbreviations.
;;; *CURRENT-LEVEL* -- interface.
;;;
(defvar *current-level* 0
"The current level we are printing at, to be compared against *PRINT-LEVEL*.
See the macro DESCEND-INTO for a handy interface to depth abbreviation.")
;;; DESCEND-INTO -- interface.
;;;
(defmacro descend-into ((object stream) &body body)
"Automatically handle *print-level* abbreviation and circularity detection.
If we are too deep, then a # is printed to STREAM and BODY is ignored.
If OBJECT isn't NIL, then it is checked to see if it is a circular
reference (see WITH-CIRCULARITY-DETECTION), and handled accordingly.
BODY should do it's output to STREAM (which might be rebound)."
(if object
(once-only ((object object))
`(if (and (null *print-readably*)
*print-level*
(>= *current-level* *print-level*)
(or (null *current-structure*)
(not (eq *current-structure* ,object))))
(write-char #\# ,stream)
(with-circularity-detection (,object ,stream)
(let ((*current-level*
(if (or (null *current-structure*)
(not (eq *current-structure* ,object)))
(1+ *current-level*)
*current-level*)))
,@body))))
`(if (and (null *print-readably*)
*print-level*
(>= *current-level* *print-level*))
(write-char #\# ,stream)
(let ((*current-structure* nil)
(*current-level* (1+ *current-level*)))
,@body))))
;;; PUNT-IF-TOO-LONG -- interface.
;;;
(defmacro punt-if-too-long (index stream)
"Punt if INDEX is equal or larger then *PRINT-LENGTH* (and *PRINT-READABLY*
is NIL by outputting \"...\" and throwing to the block named NIL."
`(when (and (not *print-readably*)
*print-length*
(>= ,index *print-length*))
(write-string "..." ,stream)
(return)))
;;;; OUTPUT-OBJECT -- the main entry point.
;;; *PRETTY-PRINTER* -- public.
;;;
(defvar *pretty-printer* nil
"The current pretty printer. Should be either a function that takes two
arguments (the object and the stream) or NIL to indicate that there is
no pretty printer installed.")
;;; OUTPUT-OBJECT -- interface.
;;;
(defun output-object (object stream)
"Output OBJECT to STREAM observing all printer control variables."
(if *print-pretty*
(if *pretty-printer*
(funcall *pretty-printer* object stream)
(let ((*print-pretty* nil))
(output-ugly-object object stream)))
(output-ugly-object object stream)))
;;; OUTPUT-UGLY-OBJECT -- interface.
;;;
(defun output-ugly-object (object stream)
"Output OBJECT to STREAM observing all printer control variables except
for *PRINT-PRETTY*. Note: if *PRINT-PRETTY* is non-NIL, then the pretty
printer will be used for any components of OBJECT, just not for OBJECT
itself."
(typecase object
(fixnum
(output-integer object stream))
(list
(if (null object)
(output-symbol object stream)
(output-list object stream)))
(structure
(output-structure object stream))
(function
(if (and (fboundp 'funcallable-instance-p)
(funcallable-instance-p object))
(pcl:print-object object stream)
(output-function object stream)))
(symbol
(output-symbol object stream))
(number
(etypecase object
(integer
(output-integer object stream))
(float
(output-float object stream))
(ratio
(output-ratio object stream))
(ratio
(output-ratio object stream))
(complex
(output-complex object stream))))
(character
(output-character object stream))
(vector
(output-vector object stream))
(array
(output-array object stream))
(system-area-pointer
(output-sap object stream))
(weak-pointer
(output-weak-pointer object stream))
(t
(output-random object stream))))
;;;; Symbols.
(defvar *previous-case* ()
"What the previous case selection the printer was set to.")
;;; This variable contains the current definition of one of three symbol
;;; printers. SETUP-PRINTER-STATE sets this variable.
;;;
(defvar *internal-symbol-output-function* nil)
;;; SETUP-PRINTER-STATE -- Internal.
;;;
;;; This function sets the internal global symbol
;;; *internal-symbol-output-function* to the right function depending on the
;;; value of *print-case*. See the manual for details. The print buffer
;;; stream is also reset.
;;;
(defun setup-printer-state ()
(unless (eq *print-case* *previous-case*)
(setq *previous-case* *print-case*)
(setq *internal-symbol-output-function*
(case *print-case*
(:upcase #'output-uppercase-symbol)
(:downcase #'output-lowercase-symbol)
(:capitalize #'output-capitalize-symbol)
(T (let ((bad-case *print-case*))
(setq *print-case* :upcase)
(Error "Invalid *print-case* value: ~s" bad-case)))))))
(defun output-symbol (object stream)
(if (or *print-escape* *print-readably*)
(let ((package (symbol-package object))
(name (symbol-name object)))
(setup-printer-state)
(cond
;; If the symbol's home package is the current one, then a
;; prefix is never necessary.
((eq package *package*))
;; If the symbol is in the keyword package, output a colon.
((eq package *keyword-package*)
(write-char #\: stream))
;; Uninterned symbols print with a leading #:.
((null package)
(when (or *print-circle* *print-readably*)
(let ((marker (check-for-circularity object t)))
(case marker
((:initiate nil))
(t
(unless (handle-circularity marker stream)
(return-from output-symbol nil))))))
(when (or *print-gensym* *print-readably*)
(write-string "#:" stream)))
(t
(multiple-value-bind (symbol accessible)
(find-symbol name *package*)
;; If we can find the symbol by looking it up, it need not be
;; qualified. This can happen if the symbol has been inherited
;; from a package other than its home package.
(unless (and accessible (eq symbol object))
(funcall *internal-symbol-output-function*
(package-name package)
stream)
(multiple-value-bind (symbol externalp)
(find-external-symbol name package)
(declare (ignore symbol))
(if externalp
(write-char #\: stream)
(write-string "::" stream)))))))
(funcall *internal-symbol-output-function* name stream))
(case *print-case*
(:upcase
(write-string (symbol-name object) stream))
(:downcase
(write-string (string-downcase (symbol-name object)) stream))
(:capitalize
(write-string (string-capitalize (symbol-name object))
stream)))))
;;;; Escaping symbols:
;;; When we print symbols we have to figure out if they need to be
;;; printed with escape characters. This isn't a whole lot easier than
;;; reading symbols in the first place.
;;;
;;; For each character, the value of the corresponding element is a fixnum
;;; with bits set corresponding to attributes that the character has. This
;;; is also used by the character printer.
;;;
(defvar character-attributes
(make-array char-code-limit :element-type '(unsigned-byte 8)
:initial-element 0))
(eval-when (compile load eval)
;;; Constants which are a bit-mask for each interesting character attribute.
;;;
(defconstant number-attribute #b10) ; A numeric digit.
(defconstant letter-attribute #b100) ; A upper-case letter.
(defconstant sign-attribute #b1000) ; +-
(defconstant extension-attribute #b10000) ; ^_
(defconstant dot-attribute #b100000) ; .
(defconstant slash-attribute #b1000000) ; /
(defconstant other-attribute #b1) ; Anything else legal.
(defconstant funny-attribute #b10000000) ; Anything illegal.
(defconstant attribute-names
'((number . number-attribute) (letter . letter-attribute)
(sign . sign-attribute) (extension . extension-attribute)
(dot . dot-attribute) (slash . slash-attribute)
(other . other-attribute) (funny . funny-attribute)))
); Eval-When (compile load eval)
(flet ((set-bit (char bit)
(let ((code (char-code char)))
(setf (aref character-attributes code)
(logior bit (aref character-attributes code))))))
(dolist (char '(#\! #\@ #\$ #\% #\& #\* #\= #\~ #\[ #\] #\{ #\}
#\? #\< #\>))
(set-bit char other-attribute))
(dotimes (i 10)
(set-bit (digit-char i) number-attribute))
(do ((code (char-code #\A) (1+ code))
(end (char-code #\Z)))
((> code end))
(declare (fixnum code end))
(set-bit (code-char code) letter-attribute))
(set-bit #\- sign-attribute)
(set-bit #\+ sign-attribute)
(set-bit #\^ extension-attribute)
(set-bit #\_ extension-attribute)
(set-bit #\. dot-attribute)
(set-bit #\/ slash-attribute)
;; Make anything not explicitly allowed funny...
(dotimes (i char-code-limit)
(when (zerop (aref character-attributes i))
(setf (aref character-attributes i) funny-attribute))))
;;; For each character, the value of the corresponding element is the lowest
;;; base in which that character is a digit.
;;;
(defvar digit-bases
(make-array char-code-limit :element-type '(mod 37) :initial-element 36))
(dotimes (i 36)
(let ((char (digit-char i 36)))
(setf (aref digit-bases (char-code char)) i)))
;;; SYMBOL-QUOTEP -- Internal
;;;
;;; A FSM-like thingie that determines whether a symbol is a potential
;;; number or has evil characters in it.
;;;
(defun symbol-quotep (name)
(declare (simple-string name))
(macrolet ((advance (tag &optional (at-end t))
`(progn
(when (= index len)
,(if at-end '(go TEST-SIGN) '(return nil)))
(setq current (schar name index)
code (char-code current)
bits (aref attributes code))
(incf index)
(go ,tag)))
(test (&rest attributes)
`(not (zerop
(the fixnum
(logand
(logior ,@(mapcar
#'(lambda (x)
(or (cdr (assoc x attribute-names))
(error "Blast!")))
attributes))
bits)))))
(digitp ()
`(< (the fixnum (aref bases code)) base)))
(prog ((len (length name))
(attributes character-attributes)
(bases digit-bases)
(base *print-base*)
(index 0)
(bits 0)
(code 0)
current)
(declare (fixnum len base index bits code))
(advance START t)
TEST-SIGN ; At end, see if it is a sign...
(return (not (test sign)))
OTHER ; Not potential number, see if funny chars...
(return (not (null (%sp-find-character-with-attribute
name (1- index) len
attributes funny-attribute))))
START
(when (digitp)
(if (test letter)
(advance LAST-DIGIT-ALPHA)
(advance DIGIT)))
(when (test letter number other slash) (advance OTHER nil))
(when (char= current #\.) (advance DOT-FOUND))
(when (test sign extension) (advance START-STUFF nil))
(return t)
DOT-FOUND ; Leading dots...
(when (test letter) (advance START-DOT-MARKER nil))
(when (digitp) (advance DOT-DIGIT))
(when (test number other) (advance OTHER nil))
(when (test extension slash sign) (advance START-DOT-STUFF nil))
(when (char= current #\.) (advance DOT-FOUND))
(return t)
START-STUFF ; Leading stuff before any dot or digit.
(when (digitp)
(if (test letter)
(advance LAST-DIGIT-ALPHA)
(advance DIGIT)))
(when (test number other) (advance OTHER nil))
(when (test letter) (advance START-MARKER nil))
(when (char= current #\.) (advance START-DOT-STUFF nil))
(when (test sign extension slash) (advance START-STUFF nil))
(return t)
START-MARKER ; Number marker in leading stuff...
(when (test letter) (advance OTHER nil))
(go START-STUFF)
START-DOT-STUFF ; Leading stuff containing dot w/o digit...
(when (test letter) (advance START-DOT-STUFF nil))
(when (digitp) (advance DOT-DIGIT))
(when (test sign extension dot slash) (advance START-DOT-STUFF nil))
(when (test number other) (advance OTHER nil))
(return t)
START-DOT-MARKER ; Number marker in leading stuff w/ dot..
;; Leading stuff containing dot w/o digit followed by letter...
(when (test letter) (advance OTHER nil))
(go START-DOT-STUFF)
DOT-DIGIT ; In a thing with dots...
(when (test letter) (advance DOT-MARKER))
(when (digitp) (advance DOT-DIGIT))
(when (test number other) (advance OTHER nil))
(when (test sign extension dot slash) (advance DOT-DIGIT))
(return t)
DOT-MARKER ; Number maker in number with dot...
(when (test letter) (advance OTHER nil))
(go DOT-DIGIT)
LAST-DIGIT-ALPHA ; Previous char is a letter digit...
(when (or (digitp) (test sign slash))
(advance ALPHA-DIGIT))
(when (test letter number other dot) (advance OTHER nil))
(return t)
ALPHA-DIGIT ; Seen a digit which is a letter...
(when (or (digitp) (test sign slash))
(if (test letter)
(advance LAST-DIGIT-ALPHA)
(advance ALPHA-DIGIT)))
(when (test letter) (advance ALPHA-MARKER))
(when (test number other dot) (advance OTHER nil))
(return t)
ALPHA-MARKER ; Number marker in number with alpha digit...
(when (test letter) (advance OTHER nil))
(go ALPHA-DIGIT)
DIGIT ; Seen only real numeric digits...
(when (digitp)
(if (test letter)
(advance ALPHA-DIGIT)
(advance DIGIT)))
(when (test number other) (advance OTHER nil))
(when (test letter) (advance MARKER))
(when (test extension slash sign) (advance DIGIT))
(when (char= current #\.) (advance DOT-DIGIT))
(return t)
MARKER ; Number marker in a numeric number...
(when (test letter) (advance OTHER nil))
(go DIGIT))))
;;;; Printname hackery
;;; This function takes the pname of a symbol and adds slashes and/or
;;; vertical bars to it to make it readable again.
;;; Special quoting characters are currently vertical bar and slash who's
;;; role in life are to specially quote symbols. Funny symbol characters
;;; are those who need special slashification when they are to be printed
;;; so they can be read in again. These currently include such characters
;;; as hash signs, colons of various sorts, etc.
;;; Now there are three different version: UPPERCASE, lowercase and Captialize.
;;; Check out the manual under the entry for *print-case* for details.
(eval-when (compile eval)
(defmacro symbol-quote-char-p (char)
`(or (char= ,char #\\) (char= ,char #\|)))
); eval-when (compile eval)
(defun output-uppercase-symbol (pname stream)
(declare (simple-string pname))
(cond ((symbol-quotep pname)
(write-char #\| stream)
(dotimes (index (length pname))
(let ((char (schar pname index)))
;;If it needs slashing, do it.
(if (symbol-quote-char-p char)
(write-char #\\ stream))
(write-char char stream)))
(write-char #\| stream))
(t
(write-string pname stream))))
;;; See documentation for output-symbol-uppercase (above).
;;;
(defun output-lowercase-symbol (pname stream)
(declare (simple-string pname))
(cond ((symbol-quotep pname)
(write-char #\| stream)
(dotimes (index (length pname))
(let ((char (schar pname index)))
;;If it needs slashing, do it.
(if (symbol-quote-char-p char)
(write-char #\\ stream))
(write-char char stream)))
(write-char #\| stream))
(t
(dotimes (index (length pname))
(let ((char (schar pname index)))
(write-char (char-downcase char) stream))))))
(defun output-capitalize-symbol (pname stream)
(declare (simple-string pname))
(cond
((symbol-quotep pname)
(write-char #\| stream)
(dotimes (index (length pname))
(let ((char (schar pname index)))
;;If it needs slashing, do it.
(if (symbol-quote-char-p char)
(write-char #\\ stream))
(write-char char stream)))
(write-char #\| stream))
(t
(do ((index 0 (1+ index))
(pname-length (length (the string pname)))
(prev-not-alpha t))
((= index pname-length))
(declare (fixnum index pname-length))
(let ((char (char pname index)))
(write-char (if prev-not-alpha char (char-downcase char)) stream)
(setq prev-not-alpha (not (alpha-char-p char))))))))
;;;; Recursive objects.
(defun output-list (list stream)
(descend-into (list stream)
(write-char #\( stream)
(let ((length 0)
(list list))
(loop
(punt-if-too-long length stream)
(output-object (pop list) stream)
(unless list
(return))
(when (or (atom list) (check-for-circularity list))
(write-string " . " stream)
(output-object list stream)
(return))
(write-char #\space stream)
(incf length)))
(write-char #\) stream)))
(defun output-vector (vector stream)
(declare (vector vector))
(cond ((stringp vector)
(if (or *print-escape* *print-readably*)
(quote-string vector stream)
(write-string vector stream)))
((not (or *print-array* *print-readably*))
(output-terse-array vector stream))
((bit-vector-p vector)
(write-string "#*" stream)
(dotimes (i (length vector))
(output-object (aref vector i) stream)))
(t
(when (and *print-readably*
(not (eq (array-element-type vector) 't)))
(error "Cannot print ~S in a readable format." vector))
(descend-into (vector stream)
(write-string "#(" stream)
(dotimes (i (length vector))
(unless (zerop i)
(write-char #\space stream))
(punt-if-too-long i stream)
(output-object (aref vector i) stream))
(write-string ")" stream)))))
;;; QUOTE-STRING -- Internal.
;;;
;;; This function outputs a string quoting characters sufficiently, so someone
;;; can read it in again. Basically, put a slash in front of an character
;;; satisfying FROB.
;;;
(defun quote-string (string stream)
(macrolet ((frob (char)
;; Probably should look at readtable, but just do this for now.
`(or (char= ,char #\\)
(char= ,char #\"))))
(write-char #\" stream)
(with-array-data ((data string) (start) (end))
(do ((index start (1+ index)))
((>= index end))
(let ((char (schar data index)))
(when (frob char) (write-char #\\ stream))
(write-char char stream))))
(write-char #\" stream)))
(defun output-array (array stream)
"Outputs the printed representation of any array in either the #< or #A
form."
(if (or *print-array* *print-readably*)
(output-array-guts array stream)
(output-terse-array array stream)))
;;; Master function for outputing the #A form of an array
;;;
(defun output-array-guts (array stream)
(when (and *print-readably*
(not (eq (array-element-type array) t)))
(error "Arrays of element-type ~S cannot be printed readably."
(array-element-type array)))
(descend-into (array stream)
(write-char #\# stream)
(let ((*print-base* 10))
(output-integer (array-rank array) stream))
(write-char #\A stream)
(with-array-data ((data array) (start) (end))
(declare (ignore end))
(sub-output-array-guts data (array-dimensions array) stream start))))
(defun sub-output-array-guts (array dimensions stream index)
(declare (simple-vector array) (fixnum index))
(cond ((null dimensions)
(output-object (svref array index) stream))
(t
(descend-into (nil stream)
(write-char #\( stream)
(let* ((dimension (car dimensions))
(dimensions (cdr dimensions))
(count (reduce #'* dimensions)))
(dotimes (i dimension)
(unless (zerop i)
(write-char #\space stream))
(punt-if-too-long i stream)
(sub-output-array-guts array dimensions stream index)
(incf index count)))
(write-char #\) stream)))))
;;; Used to output the #< form of any array.
;;;
(defun output-terse-array (array stream)
(let ((*print-level* nil)
(*print-length* nil))
(print-unreadable-object (array stream :type t :identity t))))
;;; Structure Printing. These days we can always pass the buck to the
;;; Defstruct code.
(defun output-structure (structure stream)
(let ((*current-structure* nil))
(descend-into (structure stream)
(let ((*current-structure* structure))
(funcall (or (info type printer (structure-ref structure 0))
#'c::default-structure-print)
structure stream *current-level*)))))
;;;; Integer, ratio, and complex printing. (i.e. everything but floats)
(defun output-integer (integer stream)
(unless (and (fixnump *print-base*)
(< 1 *print-base* 37))
(let ((obase *print-base*))
(setq *print-base* 10.)
(error "~A is not a reasonable value for *Print-Base*." obase)))
(when (and (not (= *print-base* 10.))
*print-radix*)
;; First print leading base information, if any.
(write-char #\# stream)
(write-char (case *print-base*
(2. #\b)
(8. #\o)
(16. #\x)
(T (let ((fixbase *print-base*)
(*print-base* 10.)
(*print-radix* ()))
(sub-output-integer fixbase stream))
#\r))
stream))
;; Then output a minus sign if the number is negative, then output
;; the absolute value of the number.
(cond ((bignump integer) (print-bignum integer stream))
((< integer 0)
(write-char #\- stream)
(sub-output-integer (- integer) stream))
(t
(sub-output-integer integer stream)))
;; Print any trailing base information, if any.
(if (and (= *print-base* 10.) *print-radix*)
(write-char #\. stream)))
(defun sub-output-integer (integer stream)
(let ((quotient ())
(remainder ()))
;; Recurse until you have all the digits pushed on the stack.
(if (not (zerop (multiple-value-setq (quotient remainder)
(truncate integer *print-base*))))
(sub-output-integer quotient stream))
;; Then as each recursive call unwinds, turn the digit (in remainder)
;; into a character and output the character.
(write-char (code-char (if (and (> remainder 9.)
(> *print-base* 10.))
(+ (char-code #\A) (- remainder 10.))
(+ (char-code #\0) remainder)))
stream)))
;;;; Bignum printing
;;; Written by Steven Handerson
;;; (based on Skef's idea)
;;;
;;; Rewritten to remove assumptions about the length of fixnums for the
;;; MIPS port by William Lott.
;;;
;;; *BASE-POWER* holds the number that we keep dividing into the bignum for
;;; each *print-base*. We want this number as close to *most-positive-fixnum*
;;; as possible, i.e. (floor (log most-positive-fixnum *print-base*)).
;;;
(defparameter *base-power* (make-array 37 :initial-element nil))
;;; *FIXNUM-POWER--1* holds the number of digits for each *print-base* that
;;; fit in the corresponding *base-power*.
;;;
(defparameter *fixnum-power--1* (make-array 37 :initial-element nil))
;;; PRINT-BIGNUM -- internal.
;;;
;;; Print the bignum to the stream. We first generate the correct value for
;;; *base-power* and *fixnum-power--1* if we have not already. Then we call
;;; bignum-print-aux to do the printing.
;;;
(defun print-bignum (big stream)
(unless (aref *base-power* *print-base*)
(do ((power-1 -1 (1+ power-1))
(new-divisor *print-base* (* new-divisor *print-base*))
(divisor 1 new-divisor))
((not (fixnump new-divisor))
(setf (aref *base-power* *print-base*) divisor)
(setf (aref *fixnum-power--1* *print-base*) power-1))))
(bignum-print-aux (cond ((minusp big)
(write-char #\- stream)
(- big))
(t big))
(aref *base-power* *print-base*)
(aref *fixnum-power--1* *print-base*)
stream)
big)
;;; BIGNUM-PRINT-AUX -- internal.
;;;
(defun bignum-print-aux (big divisor power-1 stream)
(multiple-value-bind (newbig fix) (truncate big divisor)
(if (fixnump newbig)
(sub-output-integer newbig stream)
(bignum-print-aux newbig divisor power-1 stream))
(do ((zeros power-1 (1- zeros))
(base-power *print-base* (* base-power *print-base*)))
((> base-power fix)
(dotimes (i zeros) (write-char #\0 stream))
(sub-output-integer fix stream)))))
(defun output-ratio (ratio stream)
(when *print-radix*
(write-char #\# stream)
(case *print-base*
(2 (write-char #\b stream))
(8 (write-char #\o stream))
(16 (write-char #\x stream))
(t (write *print-base* :stream stream :radix nil :base 10)))
(write-char #\r stream))
(let ((*print-radix* nil))
(output-integer (numerator ratio) stream)
(write-char #\/ stream)
(output-integer (denominator ratio) stream)))
(defun output-complex (complex stream)
(write-string "#C(" stream)
(output-object (realpart complex) stream)
(write-char #\space stream)
(output-object (imagpart complex) stream)
(write-char #\) stream))
;;;; Float printing.
;;;
;;; Written by Bill Maddox
;;;
;;;
;;;
;;; FLONUM-TO-STRING (and its subsidiary function FLOAT-STRING) does most of
;;; the work for all printing of floating point numbers in the printer and in
;;; FORMAT. It converts a floating point number to a string in a free or
;;; fixed format with no exponent. The interpretation of the arguments is as
;;; follows:
;;;
;;; X - The floating point number to convert, which must not be
;;; negative.
;;; WIDTH - The preferred field width, used to determine the number
;;; of fraction digits to produce if the FDIGITS parameter
;;; is unspecified or NIL. If the non-fraction digits and the
;;; decimal point alone exceed this width, no fraction digits
;;; will be produced unless a non-NIL value of FDIGITS has been
;;; specified. Field overflow is not considerd an error at this
;;; level.
;;; FDIGITS - The number of fractional digits to produce. Insignificant
;;; trailing zeroes may be introduced as needed. May be
;;; unspecified or NIL, in which case as many digits as possible
;;; are generated, subject to the constraint that there are no
;;; trailing zeroes.
;;; SCALE - If this parameter is specified or non-NIL, then the number
;;; printed is (* x (expt 10 scale)). This scaling is exact,
;;; and cannot lose precision.
;;; FMIN - This parameter, if specified or non-NIL, is the minimum
;;; number of fraction digits which will be produced, regardless
;;; of the value of WIDTH or FDIGITS. This feature is used by
;;; the ~E format directive to prevent complete loss of
;;; significance in the printed value due to a bogus choice of
;;; scale factor.
;;;
;;; Most of the optional arguments are for the benefit for FORMAT and are not
;;; used by the printer.
;;;
;;; Returns:
;;; (VALUES DIGIT-STRING DIGIT-LENGTH LEADING-POINT TRAILING-POINT DECPNT)
;;; where the results have the following interpretation:
;;;
;;; DIGIT-STRING - The decimal representation of X, with decimal point.
;;; DIGIT-LENGTH - The length of the string DIGIT-STRING.
;;; LEADING-POINT - True if the first character of DIGIT-STRING is the
;;; decimal point.
;;; TRAILING-POINT - True if the last character of DIGIT-STRING is the
;;; decimal point.
;;; POINT-POS - The position of the digit preceding the decimal
;;; point. Zero indicates point before first digit.
;;;
;;; WARNING: For efficiency, there is a single string object *digit-string*
;;; which is modified destructively and returned as the value of
;;; FLONUM-TO-STRING. Thus the returned value is not valid across multiple
;;; calls.
;;;
;;; NOTE: FLONUM-TO-STRING goes to a lot of trouble to guarantee accuracy.
;;; Specifically, the decimal number printed is the closest possible
;;; approximation to the true value of the binary number to be printed from
;;; among all decimal representations with the same number of digits. In
;;; free-format output, i.e. with the number of digits unconstrained, it is
;;; guaranteed that all the information is preserved, so that a properly-
;;; rounding reader can reconstruct the original binary number, bit-for-bit,
;;; from its printed decimal representation. Furthermore, only as many digits
;;; as necessary to satisfy this condition will be printed.
;;;
;;;
;;; FLOAT-STRING actually generates the digits for positive numbers. The
;;; algorithm is essentially that of algorithm Dragon4 in "How to Print
;;; Floating-Point Numbers Accurately" by Steele and White. The current
;;; (draft) version of this paper may be found in [CMUC]<steele>tradix.press.
;;; DO NOT EVEN THINK OF ATTEMPTING TO UNDERSTAND THIS CODE WITHOUT READING
;;; THE PAPER!
(defvar *digits* "0123456789")
(defvar *digit-string*
(make-array 50 :element-type 'base-char :fill-pointer 0 :adjustable t
:initial-element #\?)) ; ### Hack around make-array bug.
(defun flonum-to-string (x &optional width fdigits scale fmin)
(cond ((zerop x)
;;zero is a special case which float-string cannot handle
(if fdigits
(let ((s (make-string (1+ fdigits) :initial-element #\0)))
(setf (schar s 0) #\.)
(values s (length s) t (zerop fdigits) 0))
(values "." 1 t t 0)))
(t
(setf (fill-pointer *digit-string*) 0)
(multiple-value-bind (sig exp)
(integer-decode-float x)
(let* ((precision (float-precision x))
(digits (float-digits x))
(fudge (- digits precision)))
(float-string (ash sig (- fudge)) (+ exp fudge) precision width
fdigits scale fmin))))))
(defun float-string (fraction exponent precision width fdigits scale fmin)
(let ((r fraction) (s 1) (m- 1) (m+ 1) (k 0)
(digits 0) (decpnt 0) (cutoff nil) (roundup nil) u low high)
;;Represent fraction as r/s, error bounds as m+/s and m-/s.
;;Rational arithmetic avoids loss of precision in subsequent calculations.
(cond ((> exponent 0)
(setq r (ash fraction exponent))
(setq m- (ash 1 exponent))
(setq m+ m-))
((< exponent 0)
(setq s (ash 1 (- exponent)))))
;;adjust the error bounds m+ and m- for unequal gaps
(when (= fraction (ash 1 precision))
(setq m+ (ash m+ 1))
(setq r (ash r 1))
(setq s (ash s 1)))
;;scale value by requested amount, and update error bounds
(when scale
(if (minusp scale)
(let ((scale-factor (expt 10 (- scale))))
(setq s (* s scale-factor)))
(let ((scale-factor (expt 10 scale)))
(setq r (* r scale-factor))
(setq m+ (* m+ scale-factor))
(setq m- (* m- scale-factor)))))
;;scale r and s and compute initial k, the base 10 logarithm of r
(do ()
((>= r (ceiling s 10)))
(decf k)
(setq r (* r 10))
(setq m- (* m- 10))
(setq m+ (* m+ 10)))
(do ()(nil)
(do ()
((< (+ (ash r 1) m+) (ash s 1)))
(setq s (* s 10))
(incf k))
;;determine number of fraction digits to generate
(cond (fdigits
;;use specified number of fraction digits
(setq cutoff (- fdigits))
;;don't allow less than fmin fraction digits
(if (and fmin (> cutoff (- fmin))) (setq cutoff (- fmin))))
(width
;;use as many fraction digits as width will permit
;;but force at least fmin digits even if width will be exceeded
(if (< k 0)
(setq cutoff (- 1 width))
(setq cutoff (1+ (- k width))))
(if (and fmin (> cutoff (- fmin))) (setq cutoff (- fmin)))))
;;If we decided to cut off digit generation before precision has
;;been exhausted, rounding the last digit may cause a carry propagation.
;;We can prevent this, preserving left-to-right digit generation, with
;;a few magical adjustments to m- and m+. Of course, correct rounding
;;is also preserved.
(when (or fdigits width)
(let ((a (- cutoff k))
(y s))
(if (>= a 0)
(dotimes (i a) (setq y (* y 10)))
(dotimes (i (- a)) (setq y (ceiling y 10))))
(setq m- (max y m-))
(setq m+ (max y m+))
(when (= m+ y) (setq roundup t))))
(when (< (+ (ash r 1) m+) (ash s 1)) (return)))
;;zero-fill before fraction if no integer part
(when (< k 0)
(setq decpnt digits)
(vector-push-extend #\. *digit-string*)
(dotimes (i (- k))
(incf digits) (vector-push-extend #\0 *digit-string*)))
;;generate the significant digits
(do ()(nil)
(decf k)
(when (= k -1)
(vector-push-extend #\. *digit-string*)
(setq decpnt digits))
(multiple-value-setq (u r) (truncate (* r 10) s))
(setq m- (* m- 10))
(setq m+ (* m+ 10))
(setq low (< (ash r 1) m-))
(if roundup
(setq high (>= (ash r 1) (- (ash s 1) m+)))
(setq high (> (ash r 1) (- (ash s 1) m+))))
;;stop when either precision is exhausted or we have printed as many
;;fraction digits as permitted
(when (or low high (and cutoff (<= k cutoff))) (return))
(vector-push-extend (char *digits* u) *digit-string*)
(incf digits))
;;if cutoff occured before first digit, then no digits generated at all
(when (or (not cutoff) (>= k cutoff))
;;last digit may need rounding
(vector-push-extend (char *digits*
(cond ((and low (not high)) u)
((and high (not low)) (1+ u))
(t (if (<= (ash r 1) s) u (1+ u)))))
*digit-string*)
(incf digits))
;;zero-fill after integer part if no fraction
(when (>= k 0)
(dotimes (i k) (incf digits) (vector-push-extend #\0 *digit-string*))
(vector-push-extend #\. *digit-string*)
(setq decpnt digits))
;;add trailing zeroes to pad fraction if fdigits specified
(when fdigits
(dotimes (i (- fdigits (- digits decpnt)))
(incf digits)
(vector-push-extend #\0 *digit-string*)))
;;all done
(values *digit-string* (1+ digits) (= decpnt 0) (= decpnt digits) decpnt)))
;;; SCALE-EXPONENT -- Internal
;;;
;;; Given a non-negative floating point number, SCALE-EXPONENT returns a new
;;; floating point number Z in the range (0.1, 1.0] and and exponent E such
;;; that Z * 10^E is (approximately) equal to the original number. There may
;;; be some loss of precision due the floating point representation. The
;;; scaling is always done with long float arithmetic, which helps printing of
;;; lesser precisions as well as avoiding generic arithmetic.
;;;
;;; When computing our initial scale factor using EXPT, we pull out part of
;;; the computation to avoid over/under flow. When denormalized, we must pull
;;; out a large factor, since there is more negative exponent range than
;;; positive range.
;;;
(defun scale-exponent (original-x)
(let* ((x (coerce original-x 'long-float)))
(multiple-value-bind (sig exponent)
(decode-float x)
(declare (ignore sig))
(if (= x 0.0l0)
(values (float 0.0l0 original-x) 1)
(let* ((ex (round (* exponent (log 2l0 10))))
(x (if (minusp ex)
(if (float-denormalized-p x)
(* x 1.0l16 (expt 10.0l0 (- (- ex) 16)))
(* x 10.0l0 (expt 10.0l0 (- (- ex) 1))))
(/ x 10.0l0 (expt 10.0l0 (1- ex))))))
(do ((d 10.0l0 (* d 10.0l0))
(y x (/ x d))
(ex ex (1+ ex)))
((< y 1.0l0)
(do ((m 10.0l0 (* m 10.0l0))
(z y (* y m))
(ex ex (1- ex)))
((>= z 0.1l0)
(values (float z original-x) ex))))))))))
;;;; Entry point for the float printer.
;;; Entry point for the float printer as called by PRINT, PRIN1, PRINC,
;;; etc. The argument is printed free-format, in either exponential or
;;; non-exponential notation, depending on its magnitude.
;;;
;;; NOTE: When a number is to be printed in exponential format, it is scaled in
;;; floating point. Since precision may be lost in this process, the
;;; guaranteed accuracy properties of FLONUM-TO-STRING are lost. The
;;; difficulty is that FLONUM-TO-STRING performs extensive computations with
;;; integers of similar magnitude to that of the number being printed. For
;;; large exponents, the bignums really get out of hand. If bignum arithmetic
;;; becomes reasonably fast and the exponent range is not too large, then it
;;; might become attractive to handle exponential notation with the same
;;; accuracy as non-exponential notation, using the method described in the
;;; Steele and White paper.
;;; PRINT-FLOAT-EXPONENT -- Internal
;;;
;;; Print the appropriate exponent marker for X and the specified exponent.
;;;
(defun print-float-exponent (x exp stream)
(declare (float x) (integer exp) (stream stream))
(let ((*print-radix* nil)
(plusp (plusp exp)))
(if (typep x *read-default-float-format*)
(unless (eql exp 0)
(format stream "e~:[~;+~]~D" plusp exp))
(format stream "~A~:[~;+~]~D"
(etypecase x
(single-float #\f)
(double-float #\d)
(short-float #\s)
(long-float #\L))
plusp exp))))
;;; FLOAT-FORMAT-NAME -- Internal
;;;
;;; Return the string name of X's float format.
;;;
(defun float-format-name (x)
(declare (float x))
(etypecase x
(single-float "SINGLE-FLOAT")
(double-float "DOUBLE-FLOAT")
(short-float "SHORT-FLOAT")
(long-float "LONG-FLOAT")))
;;; OUTPUT-FLOAT-INFINITY -- Internal
;;;
;;; Write out an infinity using #. notation, or flame out if
;;; *print-readably* is true and *read-eval* is false.
;;;
(defun output-float-infinity (x stream)
(declare (float x) (stream stream))
(cond (*read-eval*
(write-string "#." stream))
(*print-readably*
(error "Unable to print infinities readably without #."))
(t
(write-string "#<" stream)))
(write-string "EXT:" stream)
(write-string (float-format-name x) stream)
(write-string (if (plusp x) "-POSITIVE-" "-NEGATIVE-")
stream)
(write-string "INFINITY" stream)
(unless *read-eval*
(write-string ">" stream)))
;;; OUTPUT-FLOAT-NAN -- Internal
;;;
;;; Output a #< NaN or die trying.
;;;
(defun output-float-nan (x stream)
(when *print-readably*
(error "Can't print NaN's readably."))
(write-string "#<" stream)
(write-string (float-format-name x) stream)
(write-string (if (float-trapping-nan-p x) " Trapping" " Quiet") stream)
(write-string " NaN>" stream))
;;; OUTPUT-FLOAT -- Internal
;;;
;;; Functioned called by OUTPUT-OBJECT to handle floats.
;;;
(defun output-float (x stream)
(cond
((float-infinity-p x)
(output-float-infinity x stream))
((float-nan-p x)
(output-float-nan x stream))
(t
(let ((x (cond ((minusp (float-sign x))
(write-char #\- stream)
(- x))
(t
x))))
(cond
((zerop x)
(write-string "0.0" stream)
(print-float-exponent x 0 stream))
(t
(output-float-aux x stream (float 1/1000 x) (float 10000000 x))))))))
;;;
(defun output-float-aux (x stream e-min e-max)
(if (and (>= x e-min) (< x e-max))
;;free format
(multiple-value-bind (str len lpoint tpoint)
(flonum-to-string x)
(declare (ignore len))
(when lpoint (write-char #\0 stream))
(write-string str stream)
(when tpoint (write-char #\0 stream))
(print-float-exponent x 0 stream))
;;exponential format
(multiple-value-bind (f ex)
(scale-exponent x)
(multiple-value-bind (str len lpoint tpoint)
(flonum-to-string f nil nil 1)
(declare (ignore len))
(when lpoint (write-char #\0 stream))
(write-string str stream)
(when tpoint (write-char #\0 stream))
;; subtract out scale factor of 1 passed to flonum-to-string
(print-float-exponent x (1- ex) stream)))))
;;;; Other leaf objects.
;;; OUTPUT-CHARACTER -- Internal
;;;
;;; If *print-escape* is false, just do a WRITE-CHAR, otherwise output the
;;; character name or the character in the #\char format.
;;;
(defun output-character (char stream)
(if (or *print-escape* *print-readably*)
(let ((name (char-name char)))
(write-string "#\\" stream)
(if name
(write-string name stream)
(write-char char stream)))
(write-char char stream)))
(defun output-sap (sap stream)
(declare (type system-area-pointer sap))
(cond (*read-eval*
(format stream "#.(~S #x~8,'0X)"
'int-sap (sap-int sap)))
((not *print-readably*)
(format stream "#<System-Area-Pointer: #x~8,'0X>"
(sap-int sap)))
(t
(error "Cannot print system-area-pointers with *READ-EVAL* NIL and ~
*PRINT-READABLY* T."))))
(defun output-weak-pointer (weak-pointer stream)
(declare (type weak-pointer weak-pointer))
(when *print-readably*
(error "Cannot print weak poinrts with *PRINT-READABLY* T."))
(multiple-value-bind
(value validp)
(weak-pointer-value weak-pointer)
(cond (validp
(write-string "#<Weak Pointer: " stream)
(write value :stream stream)
(write-char #\> stream))
(t
(write-string "#<Broken Weak Pointer>" stream)))))
;;;; Various flavors of function pointers.
;;; OUTPUT-FUNCTION-OBJECT outputs the main part of the printed
;;; representation of function objects. It is called from OUTPUT-RANDOM
;;; below.
(defun output-function-object (subr stream)
(let ((name (%primitive c::function-name subr)))
(write-string "Function " stream)
(prin1 name stream)))
;;; OUTPUT-INTERPRETED-FUNCTION -- Internal
;;;
;;; Print the name or definition of an interpreted function.
;;;
(defun output-interpreted-function (subr stream)
(multiple-value-bind
(def ignore name)
(eval:interpreted-function-lambda-expression subr)
(declare (ignore ignore))
(let ((*print-level* 3))
(format stream "Interpreted Function ~S" (or name def)))))
(defun output-function (function stream)
(print-unreadable-object (function stream :identity t)
(case (get-type function)
((#.vm:function-header-type #.vm:closure-function-header-type)
(output-function-object function stream))
(#.vm:closure-header-type
(cond
((eval:interpreted-function-p function)
(output-interpreted-function function stream))
(t
(write-string "Closure Over " stream)
(output-function-object (%primitive c::closure-function function)
stream)))))))
;;;; Catch-all for unknown things.
(defun output-random (object stream)
(print-unreadable-object (object stream :identity t)
(let ((lowtag (get-lowtag object)))
(case lowtag
(#.vm:other-pointer-type
(let ((type (get-type object)))
(case type
(#.vm:code-header-type
(let ((dinfo (code-header-ref object vm:code-debug-info-slot)))
(cond ((eq dinfo :bogus-lra)
(write-string "Bogus Code Object" stream))
(t
(write-string "Code Object" stream)
(when dinfo
(write-char #\space stream)
(output-object (c::compiled-debug-info-name dinfo)
stream))))))
(#.vm:return-pc-header-type
(write-string "Return PC Object" stream))
(#.vm:value-cell-header-type
(write-string "Value Cell " stream)
(output-object (%primitive value-cell-ref object) stream))
(t
(write-string "Unknown Pointer Object, type=" stream)
(let ((*print-base* 16) (*print-radix* t))
(output-integer type stream))))))
((#.vm:function-pointer-type
#.vm:structure-pointer-type
#.vm:list-pointer-type)
(write-string "Unknown Pointer Object, type=" stream))
(t
(case (get-type object)
(#.vm:unbound-marker-type
(write-string "Unbound Marker"))
(t
(write-string "Unknown Immediate Object, lowtag=" stream)
(let ((*print-base* 2) (*print-radix* t))
(output-integer lowtag stream))
(write-string ", type=" stream)
(let ((*print-base* 16) (*print-radix* t))
(output-integer (get-type object) stream)))))))))