1.0.18.10: Record filenames in DEBUG-SOURCEs during EVAL-WHEN, LOAD.
[sbcl.git] / src / code / describe.lisp
1 ;;;; most of the DESCRIBE system -- 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 (declaim (ftype (function (t stream)) describe-object))
16 (defgeneric describe-object (x stream))
17
18 (defun describe (x &optional (stream-designator *standard-output*))
19   #+sb-doc
20   "Print a description of the object X."
21   (let ((stream (out-synonym-of stream-designator)))
22     ;; Until sbcl-0.8.0.x, we did
23     ;;   (FRESH-LINE STREAM)
24     ;;   (PPRINT-LOGICAL-BLOCK (STREAM NIL)
25     ;;     ...
26     ;; here. However, ANSI's specification of DEFUN DESCRIBE,
27     ;;   DESCRIBE exists as an interface primarily to manage argument
28     ;;   defaulting (including conversion of arguments T and NIL into
29     ;;   stream objects) and to inhibit any return values from
30     ;;   DESCRIBE-OBJECT.
31     ;; doesn't mention either FRESH-LINEing or PPRINT-LOGICAL-BLOCKing,
32     ;; and the example of typical DESCRIBE-OBJECT behavior in ANSI's
33     ;; specification of DESCRIBE-OBJECT will work poorly if we do them
34     ;; here. (The example method for DESCRIBE-OBJECT does its own
35     ;; FRESH-LINEing, which is a physical directive which works poorly
36     ;; inside a pretty-printer logical block.)
37     (describe-object x stream)
38     ;; We don't TERPRI here either (any more since sbcl-0.8.0.x), because
39     ;; again ANSI's specification of DESCRIBE doesn't mention it and
40     ;; ANSI's example of DESCRIBE-OBJECT does its own final TERPRI.
41     )
42   (values))
43 \f
44 ;;;; miscellaneous DESCRIBE-OBJECT methods
45
46 (defmethod describe-object ((x t) s)
47   (format s "~&~@<~S ~_is a ~S.~:>~%" x (type-of x)))
48
49 (defmethod describe-object ((x cons) s)
50   (call-next-method)
51   (when (and (legal-fun-name-p x)
52              (fboundp x))
53     (%describe-fun (fdefinition x) s :function x)
54     ;;was: (format s "~@:_Its FDEFINITION is ~S.~@:_" (fdefinition x))
55     ;; TO DO: should check for SETF documentation.
56     ;; TO DO: should make it clear whether the definition is a
57     ;; DEFUN (SETF FOO) or DEFSETF FOO or what.
58     ))
59
60 (defmethod describe-object ((x array) s)
61   (fresh-line s)
62   (pprint-logical-block (s nil)
63     (cond
64      ((= 1 (array-rank x))
65       (format s "~S is a vector with ~D elements."
66               x (car (array-dimensions x)))
67       (when (array-has-fill-pointer-p x)
68         (format s "~@:_It has a fill pointer value of ~S."
69                 (fill-pointer x))))
70      (t
71       (format s "~S is an array of dimension ~:S."
72               x (array-dimensions x))))
73     (let ((array-element-type (array-element-type x)))
74       (unless (eq array-element-type t)
75         (format s
76                 "~@:_Its element type is specialized to ~S."
77                 array-element-type)))
78     (if (and (array-header-p x) (%array-displaced-p x))
79         (format s "~@:_The array is displaced with offset ~S."
80                 (%array-displacement x))))
81   (terpri s))
82
83 (defmethod describe-object ((x hash-table) s)
84   (declare (type stream s))
85   (format s "~&~@<~S ~_is an ~S hash table.~:>" x (hash-table-test x))
86   (format s "~&Its SIZE is ~S." (hash-table-size x))
87   (format s
88           "~&~@<Its REHASH-SIZE is ~S. ~_Its REHASH-THRESHOLD is ~S.~:>"
89           (hash-table-rehash-size x)
90           (hash-table-rehash-threshold x))
91   (fresh-line s)
92   (pprint-logical-block (s nil)
93     (let ((count (hash-table-count x)))
94       (format s "It holds ~S key/value pair~:P~:[: ~2I~_~;.~]"
95               count (zerop count))
96       (let ((n 0))
97         (declare (type index n))
98         (dohash ((k v) x :locked t)
99           (unless (zerop n)
100             (write-char #\space s))
101           (incf n)
102           (when (and *print-length* (> n *print-length*))
103             (format s "~:_...")
104             (return))
105           (format s "~:_(~@<~S ~:_~S~:>)" k v)))))
106   (terpri s))
107
108 (defmethod describe-object ((condition condition) s)
109   (sb-kernel:describe-condition condition s))
110 \f
111 ;;;; DESCRIBE-OBJECT methods for symbols and functions, including all
112 ;;;; sorts of messy stuff about documentation, type information,
113 ;;;; packaging, function implementation, etc...
114
115 ;;; Print the specified kind of documentation about the given NAME. If
116 ;;; NAME is null, or not a valid name, then don't print anything.
117 (declaim (ftype (function (t stream t t) (values)) %describe-doc))
118 (defun %describe-doc (name s kind kind-doc)
119   (when (and name (typep name '(or symbol cons)))
120     (let ((doc (fdocumentation name kind)))
121       (when doc
122         (format s "~&~@(~A documentation:~)~%  ~A"
123                 (or kind-doc kind) doc))))
124   (values))
125
126 ;;; Describe various stuff about the functional semantics attached to
127 ;;; the specified NAME, if NAME is the kind of thing you can look
128 ;;; up as a name. (In the case of anonymous closures and other
129 ;;; things, it might not be.) TYPE-SPEC is the function type specifier
130 ;;; extracted from the definition, or NIL if none.
131 (declaim (ftype (function (t stream t)) %describe-fun-name))
132 (defun %describe-fun-name (name s type-spec)
133   (when (and name (typep name '(or symbol cons)))
134     (multiple-value-bind (type where)
135         (if (legal-fun-name-p name)
136             (values (type-specifier (info :function :type name))
137                     (info :function :where-from name))
138             (values type-spec :defined))
139       (when (consp type)
140         (format s "~&Its ~(~A~) argument types are:~%  ~S"
141                 where (second type))
142         (format s "~&Its result type is:~%  ~S" (third type))))
143     (let ((inlinep (info :function :inlinep name)))
144       (when inlinep
145         (format s
146                 "~&It is currently declared ~(~A~);~
147                  ~:[no~;~] expansion is available."
148                 inlinep (info :function :inline-expansion-designator name))))))
149
150 ;;; Print information from the debug-info about where CODE-OBJ was
151 ;;; compiled from.
152 (defun %describe-compiled-from (code-obj s)
153   (declare (type stream s))
154   (let ((info (sb-kernel:%code-debug-info code-obj)))
155     (when info
156       (let ((source (sb-c::debug-info-source info)))
157         (when source
158           (format s "~&On ~A it was compiled from:"
159                   ;; FIXME: The FORMAT-UNIVERSAL-TIME calls in the system
160                   ;; should become more consistent, probably not using
161                   ;; any nondefault options.
162                   (format-universal-time nil (sb-c::debug-source-compiled source)
163                                          :style :abbreviated))
164           (let ((name (sb-c::debug-source-namestring source)))
165             (cond (name
166                    (format s "~&~A~@:_  Created: " name)
167                    (format-universal-time s (sb-c::debug-source-created source)))
168                   ((sb-di:debug-source-form source)
169                    (format s "~&  ~S" (sb-di:debug-source-form source)))
170                   (t (bug "Don't know how to use a DEBUG-SOURCE without ~
171                            a namestring or a form.")))))))))
172
173 ;;; Describe a compiled function. The closure case calls us to print
174 ;;; the guts.
175 (defun %describe-fun-compiled (x s kind name)
176   (declare (type stream s))
177   (let ((args (%simple-fun-arglist x)))
178     (cond ((not args)
179            (write-string "  There are no arguments." s))
180           (t
181            (format s "~&~@(The ~@[~A's ~]arguments are:~@:_~)" kind)
182            (write-string "  " s)
183             (let ((*print-pretty* t)
184                   (*print-escape* t)
185                   (*print-base* 10)
186                   (*print-radix* nil))
187               (pprint-logical-block (s nil)
188                  (pprint-indent :current 2)
189                  (format s "~A" args))))))
190   (let ((name (or name (%simple-fun-name x))))
191     (%describe-doc name s 'function kind)
192     (unless (eq kind :macro)
193       (%describe-fun-name name s (%simple-fun-type x))))
194   (%describe-compiled-from (sb-kernel:fun-code-header x) s))
195
196 (defun %describe-fun (x s &optional (kind :function) (name nil))
197   (etypecase x
198     #+sb-eval
199     (sb-eval:interpreted-function
200      (%describe-interpreted-fun x s kind name))
201     (function
202      (%describe-compiled-fun x s kind name))))
203
204 ;;; Describe a function object. KIND and NAME provide some information
205 ;;; about where the function came from.
206 (defun %describe-compiled-fun (x s &optional (kind :function) (name nil))
207   (declare (type function x))
208   (declare (type stream s))
209   (declare (type (member :macro :function) kind))
210   (fresh-line s)
211   (pprint-logical-block (s nil)
212     (ecase kind
213       (:macro (format s "Macro-function: ~S" x))
214       (:function (if name
215                      (format s "Function: ~S" x)
216                      (format s "~S is a function." x))))
217     (format s "~@:_~@<Its associated name (as in ~S) is ~2I~_~S.~:>"
218             'function-lambda-expression
219             (nth-value 2 (function-lambda-expression x)))
220     (case (widetag-of x)
221       (#.sb-vm:closure-header-widetag
222        (%describe-fun-compiled (%closure-fun x) s kind name)
223        (format s "~&Its closure environment is:")
224        (loop for value in (%closure-values x)
225           for i = 0 then (1+ i)
226           do (format s "~&  ~S: ~S" i value)))
227       (#.sb-vm:simple-fun-header-widetag
228        (%describe-fun-compiled x s kind name))
229       (#.sb-vm:funcallable-instance-header-widetag
230        ;; Only STANDARD-GENERIC-FUNCTION would be handled here, but
231        ;; since it has its own DESCRIBE-OBJECT method, it should've been
232        ;; picked off before getting here. So hopefully we never get here.
233        (format s "~@:_It is an unknown type of funcallable instance."))
234       (t
235        (format s "~@:_It is an unknown type of function."))))
236   (terpri s))
237
238 ;; Describe an interpreted function.
239 #+sb-eval
240 (defun %describe-interpreted-fun (x s &optional (kind :function) (name nil))
241   (declare (type sb-eval:interpreted-function x))
242   (declare (type stream s))
243   (declare (type (member :macro :function) kind))
244   (fresh-line s)
245   (pprint-logical-block (s nil)
246     (ecase kind
247       (:macro (format s "Macro-function: ~S" x))
248       (:function (if name
249                      (format s "Function: ~S" x)
250                      (format s "~S is a function." x))))
251     (format s "~@:_~@<Its associated name (as in ~S) is ~2I~_~S.~:>"
252             'function-lambda-expression
253             (nth-value 2 (function-lambda-expression x)))
254     (format s "~&It is an interpreted function.~%")
255     (let ((args (sb-eval:interpreted-function-lambda-list x)))
256       (cond ((not args)
257              (write-string "There are no arguments." s))
258             (t
259              (format s "~&~@(The ~@[~A's ~]arguments are:~@:_~)" kind)
260              (write-string "  " s)
261              (let ((*print-pretty* t)
262                    (*print-escape* t)
263                    (*print-base* 10)
264                    (*print-radix* nil))
265                (pprint-logical-block (s nil)
266                  (pprint-indent :current 2)
267                  (format s "~A" args)))))
268       (format s "~&It was defined as: ")
269       (let ((*print-pretty* t)
270             (*print-escape* t)
271             (*print-base* 10)
272             (*print-radix* nil))
273         (pprint-logical-block (s nil)
274           (pprint-indent :current 2)
275           (format s "~A" (function-lambda-expression x))))))
276   (terpri s))
277
278 (defmethod describe-object ((x function) s)
279   (%describe-fun x s :function))
280
281 (defgeneric describe-symbol-fdefinition (function stream &key name))
282
283 (defmethod describe-symbol-fdefinition ((fun function) stream &key name)
284   (%describe-fun fun stream :function name))
285
286 (defmethod describe-symbol-fdefinition ((fun standard-generic-function) stream
287                                         &key name)
288   (declare (ignore name))
289   ;; Just delegate.
290   (describe-object fun stream))
291
292 (defmethod describe-object ((x symbol) s)
293   (declare (type stream s))
294
295   ;; Describe the packaging.
296   (let ((package (symbol-package x)))
297     (if package
298         (multiple-value-bind (symbol status)
299             (find-symbol (symbol-name x) package)
300           (declare (ignore symbol))
301           (format s "~&~@<~S is ~_an ~(~A~) symbol ~_in ~S.~:>"
302                   x status (symbol-package x)))
303         (format s "~&~@<~S is ~_an uninterned symbol.~:>" x)))
304   ;; TO DO: We could grovel over all packages looking for and
305   ;; reporting other phenomena, e.g. IMPORT and SHADOW, or
306   ;; availability in some package even after (SYMBOL-PACKAGE X) has
307   ;; been set to NIL.
308
309   ;; Describe the value cell.
310   (let* ((kind (info :variable :kind x))
311          (wot (ecase kind
312                 (:special "special variable")
313                 (:macro "symbol macro")
314                 (:constant "constant")
315                 (:global "undefined variable")
316                 (:alien nil))))
317     (pprint-logical-block (s nil)
318       (cond
319        ((eq kind :alien)
320         (let ((info (info :variable :alien-info x)))
321           (format s "~&~@<It is an alien at #X~8,'0X of type ~3I~:_~S.~:>"
322                   (sap-int (eval (sb-alien::heap-alien-info-sap-form info)))
323                   (sb-alien-internals:unparse-alien-type
324                    (sb-alien::heap-alien-info-type info)))
325           (format s "~&~@<Its current value is ~3I~:_~S.~:>"
326                   (eval x))))
327        ((eq kind :macro)
328         (let ((expansion (info :variable :macro-expansion x)))
329           (format s "~&It is a ~A with expansion ~S." wot expansion)))
330        ((boundp x)
331         (format s "~&~@<It is a ~A; its ~_value is ~S.~:>"
332                 wot (symbol-value x)))
333        ((not (eq kind :global))
334         (format s "~&~@<It is a ~A; no current value.~:>" wot)))
335
336       (when (eq (info :variable :where-from x) :declared)
337         (format s "~&~@<Its declared type ~_is ~S.~:>"
338                 (type-specifier (info :variable :type x)))))
339
340     (%describe-doc x s 'variable kind))
341
342   ;; Print out properties.
343   (format s "~@[~&Its SYMBOL-PLIST is ~@<~2I~_~S~:>.~]" (symbol-plist x))
344
345   ;; Describe the function cell.
346   (cond ((macro-function x)
347          (%describe-fun (macro-function x) s :macro x))
348         ((special-operator-p x)
349          (%describe-doc x s :function "Special form"))
350         ((fboundp x)
351          (describe-symbol-fdefinition (fdefinition x) s :name x)))
352
353   ;; Print other documentation.
354   (%describe-doc x s 'structure "Structure")
355   (%describe-doc x s 'type "Type")
356   (%describe-doc x s 'setf "Setf macro")
357   (dolist (assoc (info :random-documentation :stuff x))
358     (let ((type (car assoc)))
359       (format s
360               "~&~@<Documentation on the ~(~A~):~@:_~A~:>"
361               (case type
362                 ((optimize) "optimize quality")
363                 (t (car assoc)))
364               (cdr assoc))))
365
366   ;; Mention the associated type information, if any.
367   ;;
368   ;; As of sbcl-0.7.2, (INFO :TYPE :KIND X) might be
369   ;;   * :PRIMITIVE, which is handled by the FIND-CLASS case.
370   ;;   * :DEFINED, which is handled specially.
371   ;;   * :INSTANCE, which is handled by the FIND-CLASS case.
372   ;;   * :FORTHCOMING-DEFCLASS-TYPE, which is an internal-to-the-compiler
373   ;;     note that we don't try to report.
374   ;;   * NIL, in which case there's nothing to see here, move along.
375   (when (eq (info :type :kind x) :defined)
376     (format s "~&It names a type specifier."))
377   (let ((symbol-named-class (find-class x nil)))
378     (when symbol-named-class
379       (format s "~&It names a class ~A." symbol-named-class)
380       (describe symbol-named-class s)))
381
382   (terpri s))