0.7.2.4:
[sbcl.git] / src / code / describe.lisp
1 ;;;; most of the DESCRIBE mechanism -- that part which isn't derived
2 ;;;; from PCL code
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB-IMPL") ;(SB-IMPL, not SB!IMPL, since we're built in warm load.)
14 \f
15 (defvar *describe-indentation-step* 3
16   #+sb-doc
17   "the number of spaces that sets off each line of a recursive description")
18
19 (declaim (ftype (function (t stream)) describe-object))
20 (defgeneric describe-object ((x t) stream))
21
22 (defun describe (x &optional (stream-designator *standard-output*))
23   #+sb-doc
24   "Print a description of the object X."
25   (let ((stream (out-synonym-of stream-designator)))
26     (pprint-logical-block (stream nil)
27       (fresh-line stream)
28       (describe-object x stream)
29       (fresh-line stream)))
30   (values))
31 \f
32 ;;;; miscellaneous DESCRIBE-OBJECT methods
33
34 (defmethod describe-object ((x t) s)
35   (format s "~@<~S ~_is a ~S.~:>" x (type-of x)))
36
37 (defmethod describe-object ((x cons) s)
38   (call-next-method)
39   (when (and (legal-fun-name-p x)
40              (fboundp x))
41     (%describe-fun (fdefinition x) s :function x)
42     ;;was: (format s "~@:_Its FDEFINITION is ~S.~@:_" (fdefinition x))
43     ;; TO DO: should check for SETF documentation.
44     ;; TO DO: should make it clear whether the definition is a
45     ;; DEFUN (SETF FOO) or DEFSETF FOO or what.
46     ))
47
48 (defmethod describe-object ((x array) s)
49   (let ((rank (array-rank x)))
50     (cond ((> rank 1)
51            (format s "~S ~_is " x)
52            (write-string (if (%array-displaced-p x) "a displaced" "an") s)
53            (format s " array of rank ~S." rank)
54            (format s "~@:_Its dimensions are ~S." (array-dimensions x)))
55           (t
56            (format s
57                    "~@:_~S is a ~:[~;displaced ~]vector of length ~S." x
58                    (and (array-header-p x) (%array-displaced-p x)) (length x))
59            (when (array-has-fill-pointer-p x)
60              (format s "~@:_It has a fill pointer, currently ~S."
61                      (fill-pointer x))))))
62   (let ((array-element-type (array-element-type x)))
63     (unless (eq array-element-type t)
64       (format s
65               "~@:_Its element type is specialized to ~S."
66               array-element-type))))
67
68 (defmethod describe-object ((x hash-table) s)
69   (declare (type stream s))
70   (format s "~@<~S ~_is an ~S hash table.~:>" x (hash-table-test x))
71   (format s "~_Its SIZE is ~S." (hash-table-size x))
72   (format s
73           "~@:_~@<Its REHASH-SIZE is ~S. ~_Its REHASH-THRESHOLD is ~S.~:>"
74           (hash-table-rehash-size x)
75           (hash-table-rehash-threshold x))
76   (let ((count (hash-table-count x)))
77     (format s "~@:_It holds ~S key/value pair~:P~:[: ~2I~_~;.~]"
78             count (zerop count))
79     (let ((n 0))
80       (declare (type index n))
81       (dohash (k v x)
82         (unless (zerop n)
83           (write-char #\space s))
84         (incf n)
85         (when (and *print-length* (> n *print-length*))
86           (format s "~:_...")
87           (return))
88         (format s "~:_(~@<~S ~:_~S~:>)" k v)))))
89
90 (defmethod describe-object ((condition condition) s)
91   (sb-kernel:describe-condition condition s))
92 \f
93 ;;;; DESCRIBE-OBJECT methods for symbols and functions, including all
94 ;;;; sorts of messy stuff about documentation, type information,
95 ;;;; packaging, function implementation, etc..
96
97 ;;; Print the specified kind of documentation about the given NAME. If
98 ;;; NAME is null, or not a valid name, then don't print anything.
99 (declaim (ftype (function (t stream t t) (values)) %describe-doc))
100 (defun %describe-doc (name s kind kind-doc)
101   (when (and name (typep name '(or symbol cons)))
102     (let ((doc (fdocumentation name kind)))
103       (when doc
104         (format s "~_~@(~A documentation:~)~@:_  ~A"
105                 (or kind-doc kind) doc))))
106   (values))
107
108 ;;; Describe various stuff about the functional semantics attached to
109 ;;; the specified NAME, if NAME is the kind of thing you can look
110 ;;; up as a name. (In the case of anonymous closures and other
111 ;;; things, it might not be.) TYPE-SPEC is the function type specifier
112 ;;; extracted from the definition, or NIL if none.
113 (declaim (ftype (function (t stream t)) %describe-fun-name))
114 (defun %describe-fun-name (name s type-spec) 
115   (when (and name (typep name '(or symbol cons)))
116     (multiple-value-bind (type where)
117         (if (or (symbolp name) (and (listp name) (eq (car name) 'setf)))
118             (values (type-specifier (info :function :type name))
119                     (info :function :where-from name))
120             (values type-spec :defined))
121       (when (consp type)
122         (format s "~@:_Its ~(~A~) argument types are:~@:_  ~S"
123                 where (second type))
124         (format s "~@:_Its result type is:~@:_  ~S" (third type))))
125     (let ((inlinep (info :function :inlinep name)))
126       (when inlinep
127         (format s
128                 "~@:_It is currently declared ~(~A~);~
129                  ~:[no~;~] expansion is available."
130                 inlinep (info :function :inline-expansion-designator name))))))
131
132 ;;; Print information from the debug-info about where CODE-OBJ was
133 ;;; compiled from.
134 (defun %describe-compiled-from (code-obj s)
135   (declare (type stream s))
136   (let ((info (sb-kernel:%code-debug-info code-obj)))
137     (when info
138       (let ((sources (sb-c::debug-info-source info)))
139         (when sources
140           (format s "~@:_On ~A it was compiled from:"
141                   ;; FIXME: The FORMAT-UNIVERSAL-TIME calls in the system
142                   ;; should become more consistent, probably not using
143                   ;; any nondefault options.
144                   (format-universal-time nil
145                                          (sb-c::debug-source-compiled
146                                           (first sources))
147                                          :style :abbreviated))
148           (dolist (source sources)
149             (let ((name (sb-c::debug-source-name source)))
150               (ecase (sb-c::debug-source-from source)
151                 (:file
152                  (format s "~@:_~A~@:_  Created: " (namestring name))
153                  (format-universal-time s (sb-c::debug-source-created
154                                            source)))
155                 (:lisp (format s "~@:_~S" name))))))))))
156
157 ;;; Describe a compiled function. The closure case calls us to print
158 ;;; the guts.
159 (defun %describe-fun-compiled (x s kind name)
160   (declare (type stream s))
161   (let ((args (%simple-fun-arglist x)))
162     (cond ((not args)
163            (write-string "  There are no arguments." s))
164           (t
165            (format s "~@:_~@(The ~@[~A's ~]arguments are:~@:_~)" kind)
166            (write-string "  " s)
167             (let ((*print-pretty* t)
168                   (*print-escape* t)
169                   (*print-base* 10)
170                   (*print-radix* nil))
171               (pprint-logical-block (s nil)
172                  (pprint-indent :current 2)
173                  (format s "~A" args))))))
174   (let ((name (or name (%simple-fun-name x))))
175     (%describe-doc name s 'function kind)
176     (unless (eq kind :macro)
177       (%describe-fun-name name s (%simple-fun-type x))))
178   (%describe-compiled-from (sb-kernel:fun-code-header x) s))
179
180 ;;; Describe a function object. KIND and NAME provide some information
181 ;;; about where the function came from.
182 (defun %describe-fun (x s &optional (kind :function) (name nil))
183   (declare (type function x))
184   (declare (type stream s))
185   (declare (type (member :macro :function) kind))
186   (fresh-line s)
187   (ecase kind
188     (:macro (format s "Macro-function: ~S" x))
189     (:function (if name
190                    (format s "Function: ~S" x)
191                    (format s "~S is a function." x))))
192   (format s "~@:_Its associated name (as in ~S) is ~S."
193           'function-lambda-expression
194           (%fun-name x))
195   (case (widetag-of x)
196     (#.sb-vm:closure-header-widetag
197      (%describe-fun-compiled (%closure-fun x) s kind name)
198      (format s "~@:_Its closure environment is:")
199      (pprint-logical-block (s nil)
200        (pprint-indent :current 8)
201        (dotimes (i (- (get-closure-length x) (1- sb-vm:closure-info-offset)))
202          (format s "~@:_~S: ~S" i (%closure-index-ref x i)))))
203     ((#.sb-vm:simple-fun-header-widetag #.sb-vm:closure-fun-header-widetag)
204      (%describe-fun-compiled x s kind name))
205     (#.sb-vm:funcallable-instance-header-widetag
206      ;; Only STANDARD-GENERIC-FUNCTION would be handled here, but
207      ;; since it has its own DESCRIBE-OBJECT method, it should've been
208      ;; picked off before getting here. So hopefully we never get here.
209      (format s "~@:_It is an unknown type of funcallable instance."))
210     (t
211      (format s "~@:_It is an unknown type of function."))))
212
213 (defmethod describe-object ((x function) s)
214   (%describe-fun x s :function))
215
216 (defgeneric describe-symbol-fdefinition (function stream &key (name nil) ))
217
218 (defmethod describe-symbol-fdefinition ((fun function) stream &key name)
219   (%describe-fun fun stream :function name))
220
221 (defmethod describe-symbol-fdefinition ((fun standard-generic-function) stream
222                                         &key name)
223   (declare (ignore name))
224   ;; just delegate
225   (describe-object fun stream))
226
227 (defmethod describe-object ((x symbol) s)
228   (declare (type stream s))
229
230   ;; Describe the packaging.
231   (let ((package (symbol-package x)))
232     (if package
233         (multiple-value-bind (symbol status)
234             (find-symbol (symbol-name x) package)
235           (declare (ignore symbol))
236           (format s "~@<~S is ~_an ~(~A~) symbol ~_in ~S.~:>"
237                   x status (symbol-package x)))
238         (format s "~@<~S is ~_an uninterned symbol.~:>" x)))
239   ;; TO DO: We could grovel over all packages looking for and
240   ;; reporting other phenomena, e.g. IMPORT and SHADOW, or
241   ;; availability in some package even after (SYMBOL-PACKAGE X) has
242   ;; been set to NIL.
243
244   ;; Describe the value cell.
245   (let* ((kind (info :variable :kind x))
246          (wot (ecase kind
247                 (:special "special variable")
248                 (:macro "symbol macro")
249                 (:constant "constant")
250                 (:global "undefined variable")
251                 (:alien nil))))
252     (cond
253      ((eq kind :alien)
254       (let ((info (info :variable :alien-info x)))
255         (format s "~@:_~@<It is an alien at #X~8,'0X of type ~3I~:_~S.~:>~@:_"
256                 (sap-int (eval (sb-alien::heap-alien-info-sap-form info)))
257                 (sb-alien-internals:unparse-alien-type
258                  (sb-alien::heap-alien-info-type info)))
259         (format s "~@<Its current value is ~3I~:_~S.~:>"
260                 (eval x))))
261      ((eq kind :macro)
262       (let ((expansion (info :variable :macro-expansion x)))
263         (format s "~@:_It is a ~A with expansion ~S." wot expansion)))
264      ((boundp x)
265       (format s "~@:_~@<It is a ~A; its ~_value is ~S.~:>"
266               wot (symbol-value x)))
267      ((not (eq kind :global))
268       (format s "~@:_~@<It is a ~A; no current value.~:>" wot)))
269
270     (when (eq (info :variable :where-from x) :declared)
271       (format s "~@:_~@<Its declared type ~_is ~S.~:>"
272               (type-specifier (info :variable :type x))))
273
274     (%describe-doc x s 'variable kind))
275
276   ;; Print out properties.
277   (format s "~@[~@:_Its SYMBOL-PLIST is ~@<~2I~_~S~:>.~]" (symbol-plist x))
278
279   ;; Describe the function cell.
280   (cond ((macro-function x)
281          (%describe-fun (macro-function x) s :macro x))
282         ((special-operator-p x)
283          (%describe-doc x s :function "Special form"))
284         ((fboundp x)
285          (describe-symbol-fdefinition (fdefinition x) s :name x)))
286
287   ;; Print other documentation.
288   (%describe-doc x s 'structure "Structure")
289   (%describe-doc x s 'type "Type")
290   (%describe-doc x s 'setf "Setf macro")
291   (dolist (assoc (info :random-documentation :stuff x))
292     (format s
293             "~@:_Documentation on the ~(~A~):~@:_~A"
294             (car assoc)
295             (cdr assoc)))
296   
297   ;; Mention the associated type information, if any.
298   ;;
299   ;; As of sbcl-0.7.2, (INFO :TYPE :KIND X) might be
300   ;;   * :PRIMITIVE, which is handled by the FIND-CLASS case.
301   ;;   * :DEFINED, which is handled specially.
302   ;;   * :INSTANCE, which is handled by the FIND-CLASS case.
303   ;;   * :FORTHCOMING-DEFCLASS-TYPE, which is an internal-to-the-compiler
304   ;;     note that we don't try to report.
305   ;;   * NIL, in which case there's nothing to see here, move along.
306   (when (eq (info :type :kind x) :defined)
307     (format s "~@:_It names a type specifier."))
308   (let ((symbol-named-class (cl:find-class x nil)))
309     (when symbol-named-class
310       (format s "~@:_It names a class ~A." symbol-named-class)
311       (describe symbol-named-class s))))