-;;;; most of the DESCRIBE mechanism -- that part which isn't derived
+;;;; most of the DESCRIBE system -- that part which isn't derived
;;;; from PCL code
;;;; This software is part of the SBCL system. See the README file for
#+sb-doc
"Print a description of the object X."
(let ((stream (out-synonym-of stream-designator)))
- (fresh-line stream)
- (pprint-logical-block (stream nil)
- (describe-object x stream)
- (pprint-newline :mandatory stream)))
+ ;; Until sbcl-0.8.0.x, we did
+ ;; (FRESH-LINE STREAM)
+ ;; (PPRINT-LOGICAL-BLOCK (STREAM NIL)
+ ;; ...
+ ;; here. However, ANSI's specification of DEFUN DESCRIBE,
+ ;; DESCRIBE exists as an interface primarily to manage argument
+ ;; defaulting (including conversion of arguments T and NIL into
+ ;; stream objects) and to inhibit any return values from
+ ;; DESCRIBE-OBJECT.
+ ;; doesn't mention either FRESH-LINEing or PPRINT-LOGICAL-BLOCKing,
+ ;; and the example of typical DESCRIBE-OBJECT behavior in ANSI's
+ ;; specification of DESCRIBE-OBJECT will work poorly if we do them
+ ;; here. (The example method for DESCRIBE-OBJECT does its own
+ ;; FRESH-LINEing, which is a physical directive which works poorly
+ ;; inside a pretty-printer logical block.)
+ (describe-object x stream)
+ ;; We don't TERPRI here either (any more since sbcl-0.8.0.x), because
+ ;; again ANSI's specification of DESCRIBE doesn't mention it and
+ ;; ANSI's example of DESCRIBE-OBJECT does its own final TERPRI.
+ )
(values))
\f
;;;; miscellaneous DESCRIBE-OBJECT methods
(defmethod describe-object ((x t) s)
- (format s "~@<~S ~_is a ~S.~:>" x (type-of x)))
+ (format s "~&~@<~S ~_is a ~S.~:>~%" x (type-of x)))
(defmethod describe-object ((x cons) s)
(call-next-method)
))
(defmethod describe-object ((x array) s)
- (let ((rank (array-rank x)))
- (cond ((= rank 1)
- (format s
- "~@:_~S is a ~:[~;displaced ~]vector of length ~S." x
- (and (array-header-p x) (%array-displaced-p x)) (length x))
- (when (array-has-fill-pointer-p x)
- (format s "~@:_It has a fill pointer, currently ~S."
- (fill-pointer x))))
- (t
- (format s "~S ~_is " x)
- (write-string (if (%array-displaced-p x) "a displaced" "an") s)
- (format s " array of rank ~S." rank)
- (format s "~@:_Its dimensions are ~S." (array-dimensions x)))))
- (let ((array-element-type (array-element-type x)))
- (unless (eq array-element-type t)
- (format s
- "~@:_Its element type is specialized to ~S."
- array-element-type))))
+ (fresh-line s)
+ (pprint-logical-block (s nil)
+ (let ((rank (array-rank x)))
+ (cond ((= rank 1)
+ (format s
+ "~S is a ~:[~;displaced ~]vector of length ~S." x
+ (and (array-header-p x)
+ (%array-displaced-p x)
+ ) (length x))
+ (when (array-has-fill-pointer-p x)
+ (format s "~@:_It has a fill pointer, currently ~S."
+ (fill-pointer x))))
+ (t
+ (format s "~S ~_is " x)
+ (write-string (if (%array-displaced-p x) "a displaced" "an") s)
+ (format s " array of rank ~S." rank)
+ (format s "~@:_Its dimensions are ~S." (array-dimensions x)))))
+ (let ((array-element-type (array-element-type x)))
+ (unless (eq array-element-type t)
+ (format s
+ "~@:_Its element type is specialized to ~S."
+ array-element-type))))
+ (terpri s))
(defmethod describe-object ((x hash-table) s)
(declare (type stream s))
- (format s "~@<~S ~_is an ~S hash table.~:>" x (hash-table-test x))
- (format s "~_Its SIZE is ~S." (hash-table-size x))
+ (format s "~&~@<~S ~_is an ~S hash table.~:>" x (hash-table-test x))
+ (format s "~&Its SIZE is ~S." (hash-table-size x))
(format s
- "~@:_~@<Its REHASH-SIZE is ~S. ~_Its REHASH-THRESHOLD is ~S.~:>"
+ "~&~@<Its REHASH-SIZE is ~S. ~_Its REHASH-THRESHOLD is ~S.~:>"
(hash-table-rehash-size x)
(hash-table-rehash-threshold x))
- (let ((count (hash-table-count x)))
- (format s "~@:_It holds ~S key/value pair~:P~:[: ~2I~_~;.~]"
- count (zerop count))
- (let ((n 0))
- (declare (type index n))
- (dohash (k v x)
- (unless (zerop n)
- (write-char #\space s))
- (incf n)
- (when (and *print-length* (> n *print-length*))
- (format s "~:_...")
- (return))
- (format s "~:_(~@<~S ~:_~S~:>)" k v)))))
+ (fresh-line)
+ (pprint-logical-block (s nil)
+ (let ((count (hash-table-count x)))
+ (format s "It holds ~S key/value pair~:P~:[: ~2I~_~;.~]"
+ count (zerop count))
+ (let ((n 0))
+ (declare (type index n))
+ (dohash (k v x)
+ (unless (zerop n)
+ (write-char #\space s))
+ (incf n)
+ (when (and *print-length* (> n *print-length*))
+ (format s "~:_...")
+ (return))
+ (format s "~:_(~@<~S ~:_~S~:>)" k v)))))
+ (terpri s))
(defmethod describe-object ((condition condition) s)
(sb-kernel:describe-condition condition s))
\f
;;;; DESCRIBE-OBJECT methods for symbols and functions, including all
;;;; sorts of messy stuff about documentation, type information,
-;;;; packaging, function implementation, etc..
+;;;; packaging, function implementation, etc...
;;; Print the specified kind of documentation about the given NAME. If
;;; NAME is null, or not a valid name, then don't print anything.
(when (and name (typep name '(or symbol cons)))
(let ((doc (fdocumentation name kind)))
(when doc
- (format s "~_~@(~A documentation:~)~@:_ ~A"
+ (format s "~&~@(~A documentation:~)~% ~A"
(or kind-doc kind) doc))))
(values))
(info :function :where-from name))
(values type-spec :defined))
(when (consp type)
- (format s "~@:_Its ~(~A~) argument types are:~@:_ ~S"
+ (format s "~&Its ~(~A~) argument types are:~% ~S"
where (second type))
- (format s "~@:_Its result type is:~@:_ ~S" (third type))))
+ (format s "~&Its result type is:~% ~S" (third type))))
(let ((inlinep (info :function :inlinep name)))
(when inlinep
(format s
- "~@:_It is currently declared ~(~A~);~
+ "~&It is currently declared ~(~A~);~
~:[no~;~] expansion is available."
inlinep (info :function :inline-expansion-designator name))))))
(when info
(let ((sources (sb-c::debug-info-source info)))
(when sources
- (format s "~@:_On ~A it was compiled from:"
+ (format s "~&On ~A it was compiled from:"
;; FIXME: The FORMAT-UNIVERSAL-TIME calls in the system
;; should become more consistent, probably not using
;; any nondefault options.
(let ((name (sb-c::debug-source-name source)))
(ecase (sb-c::debug-source-from source)
(:file
- (format s "~@:_~A~@:_ Created: " (namestring name))
+ (format s "~&~A~@:_ Created: " (namestring name))
(format-universal-time s (sb-c::debug-source-created
source)))
- (:lisp (format s "~@:_~S" name))))))))))
+ (:lisp (format s "~&~S" name))))))))))
;;; Describe a compiled function. The closure case calls us to print
;;; the guts.
(cond ((not args)
(write-string " There are no arguments." s))
(t
- (format s "~@:_~@(The ~@[~A's ~]arguments are:~@:_~)" kind)
+ (format s "~&~@(The ~@[~A's ~]arguments are:~@:_~)" kind)
(write-string " " s)
(let ((*print-pretty* t)
(*print-escape* t)
(declare (type stream s))
(declare (type (member :macro :function) kind))
(fresh-line s)
- (ecase kind
- (:macro (format s "Macro-function: ~S" x))
- (:function (if name
- (format s "Function: ~S" x)
- (format s "~S is a function." x))))
- (format s "~@:_~@<Its associated name (as in ~S) is ~2I~_~S.~:>"
- 'function-lambda-expression
- (%fun-name x))
- (case (widetag-of x)
- (#.sb-vm:closure-header-widetag
- (%describe-fun-compiled (%closure-fun x) s kind name)
- (format s "~@:_Its closure environment is:")
- (pprint-logical-block (s nil)
- (pprint-indent :current 8)
- (dotimes (i (- (get-closure-length x) (1- sb-vm:closure-info-offset)))
- (format s "~@:_~S: ~S" i (%closure-index-ref x i)))))
- ((#.sb-vm:simple-fun-header-widetag #.sb-vm:closure-fun-header-widetag)
- (%describe-fun-compiled x s kind name))
- (#.sb-vm:funcallable-instance-header-widetag
- ;; Only STANDARD-GENERIC-FUNCTION would be handled here, but
- ;; since it has its own DESCRIBE-OBJECT method, it should've been
- ;; picked off before getting here. So hopefully we never get here.
- (format s "~@:_It is an unknown type of funcallable instance."))
- (t
- (format s "~@:_It is an unknown type of function."))))
+ (pprint-logical-block (s nil)
+ (ecase kind
+ (:macro (format s "Macro-function: ~S" x))
+ (:function (if name
+ (format s "Function: ~S" x)
+ (format s "~S is a function." x))))
+ (format s "~@:_~@<Its associated name (as in ~S) is ~2I~_~S.~:>"
+ 'function-lambda-expression
+ (%fun-name x))
+ (case (widetag-of x)
+ (#.sb-vm:closure-header-widetag
+ (%describe-fun-compiled (%closure-fun x) s kind name)
+ (format s "~@:_Its closure environment is:")
+ (pprint-logical-block (s nil)
+ (pprint-indent :current 8)
+ (dotimes (i (- (get-closure-length x) (1- sb-vm:closure-info-offset)))
+ (format s "~@:_~S: ~S" i (%closure-index-ref x i)))))
+ ((#.sb-vm:simple-fun-header-widetag #.sb-vm:closure-fun-header-widetag)
+ (%describe-fun-compiled x s kind name))
+ (#.sb-vm:funcallable-instance-header-widetag
+ ;; Only STANDARD-GENERIC-FUNCTION would be handled here, but
+ ;; since it has its own DESCRIBE-OBJECT method, it should've been
+ ;; picked off before getting here. So hopefully we never get here.
+ (format s "~@:_It is an unknown type of funcallable instance."))
+ (t
+ (format s "~@:_It is an unknown type of function."))))
+ (terpri s))
(defmethod describe-object ((x function) s)
(%describe-fun x s :function))
(defmethod describe-symbol-fdefinition ((fun standard-generic-function) stream
&key name)
(declare (ignore name))
- ;; just delegate
+ ;; Just delegate.
(describe-object fun stream))
(defmethod describe-object ((x symbol) s)
(multiple-value-bind (symbol status)
(find-symbol (symbol-name x) package)
(declare (ignore symbol))
- (format s "~@<~S is ~_an ~(~A~) symbol ~_in ~S.~:>"
+ (format s "~&~@<~S is ~_an ~(~A~) symbol ~_in ~S.~:>"
x status (symbol-package x)))
- (format s "~@<~S is ~_an uninterned symbol.~:>" x)))
+ (format s "~&~@<~S is ~_an uninterned symbol.~:>" x)))
;; TO DO: We could grovel over all packages looking for and
;; reporting other phenomena, e.g. IMPORT and SHADOW, or
;; availability in some package even after (SYMBOL-PACKAGE X) has
(let* ((kind (info :variable :kind x))
(wot (ecase kind
(:special "special variable")
- (:macro "symbol macro")
+ (:macro "symbol macro")
(:constant "constant")
(:global "undefined variable")
(:alien nil))))
- (cond
- ((eq kind :alien)
- (let ((info (info :variable :alien-info x)))
- (format s "~@:_~@<It is an alien at #X~8,'0X of type ~3I~:_~S.~:>~@:_"
- (sap-int (eval (sb-alien::heap-alien-info-sap-form info)))
- (sb-alien-internals:unparse-alien-type
- (sb-alien::heap-alien-info-type info)))
- (format s "~@<Its current value is ~3I~:_~S.~:>"
- (eval x))))
- ((eq kind :macro)
- (let ((expansion (info :variable :macro-expansion x)))
- (format s "~@:_It is a ~A with expansion ~S." wot expansion)))
- ((boundp x)
- (format s "~@:_~@<It is a ~A; its ~_value is ~S.~:>"
- wot (symbol-value x)))
- ((not (eq kind :global))
- (format s "~@:_~@<It is a ~A; no current value.~:>" wot)))
+ (pprint-logical-block (s nil)
+ (cond
+ ((eq kind :alien)
+ (let ((info (info :variable :alien-info x)))
+ (format s "~&~@<It is an alien at #X~8,'0X of type ~3I~:_~S.~:>"
+ (sap-int (eval (sb-alien::heap-alien-info-sap-form info)))
+ (sb-alien-internals:unparse-alien-type
+ (sb-alien::heap-alien-info-type info)))
+ (format s "~&~@<Its current value is ~3I~:_~S.~:>"
+ (eval x))))
+ ((eq kind :macro)
+ (let ((expansion (info :variable :macro-expansion x)))
+ (format s "~&It is a ~A with expansion ~S." wot expansion)))
+ ((boundp x)
+ (format s "~&~@<It is a ~A; its ~_value is ~S.~:>"
+ wot (symbol-value x)))
+ ((not (eq kind :global))
+ (format s "~&~@<It is a ~A; no current value.~:>" wot)))
- (when (eq (info :variable :where-from x) :declared)
- (format s "~@:_~@<Its declared type ~_is ~S.~:>"
- (type-specifier (info :variable :type x))))
+ (when (eq (info :variable :where-from x) :declared)
+ (format s "~&~@<Its declared type ~_is ~S.~:>"
+ (type-specifier (info :variable :type x)))))
(%describe-doc x s 'variable kind))
;; Print out properties.
- (format s "~@[~@:_Its SYMBOL-PLIST is ~@<~2I~_~S~:>.~]" (symbol-plist x))
+ (format s "~@[~&Its SYMBOL-PLIST is ~@<~2I~_~S~:>.~]" (symbol-plist x))
;; Describe the function cell.
(cond ((macro-function x)
((special-operator-p x)
(%describe-doc x s :function "Special form"))
((fboundp x)
- (describe-symbol-fdefinition (fdefinition x) s :name x)))
+ (describe-symbol-fdefinition (fdefinition x) s :name x)))
;; Print other documentation.
(%describe-doc x s 'structure "Structure")
(%describe-doc x s 'setf "Setf macro")
(dolist (assoc (info :random-documentation :stuff x))
(format s
- "~@:_Documentation on the ~(~A~):~@:_~A"
+ "~&~@<Documentation on the ~(~A~):~@:_~A~:>"
(car assoc)
(cdr assoc)))
;; note that we don't try to report.
;; * NIL, in which case there's nothing to see here, move along.
(when (eq (info :type :kind x) :defined)
- (format s "~@:_It names a type specifier."))
+ (format s "~&It names a type specifier."))
(let ((symbol-named-class (find-classoid x nil)))
(when symbol-named-class
- (format s "~@:_It names a class ~A." symbol-named-class)
- (describe symbol-named-class s))))
+ (format s "~&It names a class ~A." symbol-named-class)
+ (describe symbol-named-class s)))
+
+ (terpri s))
(defmethod describe-object ((object slot-object) stream)
+ (fresh-line stream)
+
(let* ((class (class-of object))
(slotds (slots-to-inspect class object))
(max-slot-name-length 0)
(class-slotds ())
(other-slotds ()))
+ (format stream "~&~@<~S ~_is an instance of class ~S.~:>" object class)
+
+ ;; Figure out a good width for the slot-name column.
(flet ((adjust-slot-name-length (name)
(setq max-slot-name-length
(max max-slot-name-length
- (length (the string (symbol-name name))))))
- (describe-slot (name value &optional (allocation () alloc-p))
- (if alloc-p
- (format stream
- "~% ~A ~S ~VT ~S"
- name allocation (+ max-slot-name-length 7) value)
- (format stream
- "~% ~A~VT ~S"
- name max-slot-name-length value))))
-
- ;; Figure out a good width for the slot-name column.
+ (length (the string (symbol-name name)))))))
(dolist (slotd slotds)
(adjust-slot-name-length (slot-definition-name slotd))
(case (slot-definition-allocation slotd)
(:instance (push slotd instance-slotds))
(:class (push slotd class-slotds))
(otherwise (push slotd other-slotds))))
- (setq max-slot-name-length (min (+ max-slot-name-length 3) 30))
- (format stream "~&~@<~S ~_is an instance of class ~S.~:>" object class)
+ (setq max-slot-name-length (min (+ max-slot-name-length 3) 30)))
- ;; Now that we know the width, we can print.
+ ;; Now that we know the width, we can print.
+ (flet ((describe-slot (name value &optional (allocation () alloc-p))
+ (if alloc-p
+ (format stream
+ "~& ~A ~S ~VT ~S"
+ name allocation (+ max-slot-name-length 7) value)
+ (format stream
+ "~& ~A~VT ~S"
+ name max-slot-name-length value))))
(when instance-slotds
- (format stream "~%The following slots have :INSTANCE allocation:")
+ (format stream "~&The following slots have :INSTANCE allocation:")
(dolist (slotd (nreverse instance-slotds))
(describe-slot
(slot-definition-name slotd)
(slot-value-or-default object
(slot-definition-name slotd)))))
(when class-slotds
- (format stream "~%The following slots have :CLASS allocation:")
+ (format stream "~&The following slots have :CLASS allocation:")
(dolist (slotd (nreverse class-slotds))
(describe-slot
(slot-definition-name slotd)
(slot-value-or-default object
(slot-definition-name slotd)))))
(when other-slotds
- (format stream "~%The following slots have allocation as shown:")
+ (format stream "~&The following slots have allocation as shown:")
(dolist (slotd (nreverse other-slotds))
(describe-slot
(slot-definition-name slotd)
(slot-value-or-default object
(slot-definition-name slotd))
- (slot-definition-allocation slotd)))))))
+ (slot-definition-allocation slotd))))))
-(defvar *describe-metaobjects-as-objects-p* nil)
+ (terpri stream))
(defmethod describe-object ((fun standard-generic-function) stream)
- (format stream "~&~A is a generic function.~%" fun)
- (format stream "Its arguments are:~% ~S~%"
+ (format stream "~&~A is a generic function." fun)
+ (format stream "~&Its arguments are:~& ~S"
(generic-function-pretty-arglist fun))
(let ((methods (generic-function-methods fun)))
(if (null methods)
- (format stream "It has no methods.~%")
+ (format stream "~&It has no methods.~%")
(let ((gf-name (generic-function-name fun)))
(format stream "Its methods are:")
(dolist (method methods)
- (format stream "~2% (~A ~{~S ~}~:S) =>~%"
+ (format stream "~2% (~A ~{~S ~}~:S) =>"
gf-name
(method-qualifiers method)
(unparse-specializers method))
- (describe-object (or (method-fast-function method)
- (method-function method))
- stream)))))
- (when *describe-metaobjects-as-objects-p*
- (call-next-method)))
+ (describe (or (method-fast-function method)
+ (method-function method))
+ stream))))))
(defmethod describe-object ((class class) stream)
(flet ((pretty-class (c) (or (class-name c) c)))
(macrolet ((ft (string &rest args) `(format stream ,string ,@args)))
- (ft "~&~S is a class, it is an instance of ~S.~%"
+ (ft "~&~S is a class. It is an instance of ~S."
class (pretty-class (class-of class)))
(let ((name (class-name class)))
(if name
(if (eq class (find-class name nil))
- (ft "Its proper name is ~S.~%" name)
- (ft "Its name is ~S, but this is not a proper name.~%" name))
+ (ft "~&Its proper name is ~S." name)
+ (ft "~&Its name is ~S, but this is not a proper name." name))
(ft "It has no name (the name is NIL).~%")))
- (ft "The direct superclasses are: ~:S, and the direct~%~
- subclasses are: ~:S. The class precedence list is:~%~S~%~
- There are ~W methods specialized for this class."
+ (ft "~&~@<The direct superclasses are: ~:S, and the direct~%~
+ subclasses are: ~:S. The class precedence list is:~2I~_~S~I~_~
+ There are ~S methods specialized for this class.~:>~%"
(mapcar #'pretty-class (class-direct-superclasses class))
(mapcar #'pretty-class (class-direct-subclasses class))
(mapcar #'pretty-class (class-precedence-list class))
- (length (specializer-direct-methods class)))))
- (when *describe-metaobjects-as-objects-p*
- (call-next-method)))
+ (length (specializer-direct-methods class))))))
(defmethod describe-object ((package package) stream)
- (pprint-logical-block (stream nil)
- (format stream "~&~S is a ~S." package (type-of package))
+ (format stream "~&~S is a ~S." package (type-of package))
+ (format stream
+ "~@[~&~@<It has nicknames ~2I~{~:_~S~^ ~}~:>~]"
+ (package-nicknames package))
+ (let* ((internal (package-internal-symbols package))
+ (internal-count (- (package-hashtable-size internal)
+ (package-hashtable-free internal)))
+ (external (package-external-symbols package))
+ (external-count (- (package-hashtable-size external)
+ (package-hashtable-free external))))
+ (format stream
+ "~&It has ~S internal and ~S external symbols."
+ internal-count external-count))
+ (flet (;; Turn a list of packages into something a human likes
+ ;; to read.
+ (humanize (package-list)
+ (sort (mapcar #'package-name package-list) #'string<)))
+ (format stream
+ "~@[~&~@<It uses packages named ~2I~{~:_~S~^ ~}~:>~]"
+ (humanize (package-use-list package)))
(format stream
- "~@[~&It has nicknames ~2I~{~:_~S~^ ~}~]"
- (package-nicknames package))
- (let* ((internal (package-internal-symbols package))
- (internal-count (- (package-hashtable-size internal)
- (package-hashtable-free internal)))
- (external (package-external-symbols package))
- (external-count (- (package-hashtable-size external)
- (package-hashtable-free external))))
- (format stream
- "~&It has ~S internal and ~S external symbols."
- internal-count external-count))
- (flet (;; Turn a list of packages into something a human likes
- ;; to read.
- (humanize (package-list)
- (sort (mapcar #'package-name package-list) #'string<)))
- (format stream
- "~@[~&It uses packages named ~2I~{~:_~S~^ ~}~]"
- (humanize (package-use-list package)))
- (format stream
- "~@[~&It is used by packages named ~2I~{~:_~S~^ ~}~]"
- (humanize (package-used-by-list package))))))
+ "~@[~&~@<It is used by packages named ~2I~{~:_~S~^ ~}~:>~]"
+ (humanize (package-used-by-list package))))
+ (terpri stream))