1;;; -*- indent-tabs-mode: nil; outline-regexp: ";;;;+" -*-
2;;;
3;;; License: Public Domain
4;;;
5;;;; Introduction
6;;;
7;;; This is the CMUCL implementation of the `swank/backend' package.
8
9(defpackage swank/cmucl
10  (:use cl swank/backend swank/source-path-parser swank/source-file-cache
11        fwrappers))
12
13(in-package swank/cmucl)
14
15(eval-when (:compile-toplevel :load-toplevel :execute)
16
17  (let ((min-version #x20c))
18    (assert (>= c:byte-fasl-file-version min-version)
19            () "This file requires CMUCL version ~x or newer" min-version))
20
21  (require 'gray-streams))
22
23
24(import-swank-mop-symbols :pcl '(:slot-definition-documentation))
25
26(defun swank-mop:slot-definition-documentation (slot)
27  (documentation slot t))
28
29;;; UTF8
30
31(locally (declare (optimize (ext:inhibit-warnings 3)))
32  ;; Compile and load the utf8 format, if not already loaded.
33  (stream::find-external-format :utf-8))
34
35(defimplementation string-to-utf8 (string)
36  (let ((ef (load-time-value (stream::find-external-format :utf-8) t)))
37    (stream:string-to-octets string :external-format ef)))
38
39(defimplementation utf8-to-string (octets)
40  (let ((ef (load-time-value (stream::find-external-format :utf-8) t)))
41    (stream:octets-to-string octets :external-format ef)))
42
43
44;;;; TCP server
45;;;
46;;; In CMUCL we support all communication styles. By default we use
47;;; `:SIGIO' because it is the most responsive, but it's somewhat
48;;; dangerous: CMUCL is not in general "signal safe", and you don't
49;;; know for sure what you'll be interrupting. Both `:FD-HANDLER' and
50;;; `:SPAWN' are reasonable alternatives.
51
52(defimplementation preferred-communication-style ()
53  :sigio)
54
55#-(or darwin mips)
56(defimplementation create-socket (host port &key backlog)
57  (let* ((addr (resolve-hostname host))
58         (addr (if (not (find-symbol "SOCKET-ERROR" :ext))
59                   (ext:htonl addr)
60                   addr)))
61    (ext:create-inet-listener port :stream :reuse-address t :host addr
62                              :backlog (or backlog 5))))
63
64;; There seems to be a bug in create-inet-listener on Mac/OSX and Irix.
65#+(or darwin mips)
66(defimplementation create-socket (host port &key backlog)
67  (declare (ignore host))
68  (ext:create-inet-listener port :stream :reuse-address t))
69
70(defimplementation local-port (socket)
71  (nth-value 1 (ext::get-socket-host-and-port (socket-fd socket))))
72
73(defimplementation close-socket (socket)
74  (let ((fd (socket-fd socket)))
75    (sys:invalidate-descriptor fd)
76    (ext:close-socket fd)))
77
78(defimplementation accept-connection (socket &key
79                                      external-format buffering timeout)
80  (declare (ignore timeout))
81  (make-socket-io-stream (ext:accept-tcp-connection socket)
82                         (ecase buffering
83                           ((t) :full)
84                           (:line :line)
85                           ((nil) :none))
86                         external-format))
87
88;;;;; Sockets
89
90(defimplementation socket-fd (socket)
91  "Return the filedescriptor for the socket represented by SOCKET."
92  (etypecase socket
93    (fixnum socket)
94    (sys:fd-stream (sys:fd-stream-fd socket))))
95
96(defun resolve-hostname (hostname)
97  "Return the IP address of HOSTNAME as an integer (in host byte-order)."
98  (let ((hostent (ext:lookup-host-entry hostname)))
99    (car (ext:host-entry-addr-list hostent))))
100
101(defvar *external-format-to-coding-system*
102  '((:iso-8859-1 "iso-latin-1-unix")
103    #+unicode
104    (:utf-8 "utf-8-unix")))
105
106(defimplementation find-external-format (coding-system)
107  (car (rassoc-if (lambda (x) (member coding-system x :test #'equal))
108                  *external-format-to-coding-system*)))
109
110(defun make-socket-io-stream (fd buffering external-format)
111  "Create a new input/output fd-stream for FD."
112  (cond (external-format
113         (sys:make-fd-stream fd :input t :output t
114                             :element-type 'character
115                             :buffering buffering
116                             :external-format external-format))
117        (t
118         (sys:make-fd-stream fd :input t :output t
119                             :element-type '(unsigned-byte 8)
120                             :buffering buffering))))
121
122(defimplementation make-fd-stream (fd external-format)
123  (make-socket-io-stream fd :full external-format))
124
125(defimplementation dup (fd)
126  (multiple-value-bind (clone error) (unix:unix-dup fd)
127    (unless clone (error "dup failed: ~a" (unix:get-unix-error-msg error)))
128    clone))
129
130(defimplementation command-line-args ()
131  ext:*command-line-strings*)
132
133(defimplementation exec-image (image-file args)
134  (multiple-value-bind (ok error)
135      (unix:unix-execve (car (command-line-args))
136			(list* (car (command-line-args))
137                               "-core" image-file
138                               "-noinit"
139                               args))
140    (error "~a" (unix:get-unix-error-msg error))
141    ok))
142
143;;;;; Signal-driven I/O
144
145(defimplementation install-sigint-handler (function)
146  (sys:enable-interrupt :sigint (lambda (signal code scp)
147                                  (declare (ignore signal code scp))
148                                  (funcall function))))
149
150(defvar *sigio-handlers* '()
151  "List of (key . function) pairs.
152All functions are called on SIGIO, and the key is used for removing
153specific functions.")
154
155(defun reset-sigio-handlers () (setq *sigio-handlers* '()))
156;; All file handlers are invalid afer reload.
157(pushnew 'reset-sigio-handlers ext:*after-save-initializations*)
158
159(defun set-sigio-handler ()
160  (sys:enable-interrupt :sigio (lambda (signal code scp)
161                                 (sigio-handler signal code scp))))
162
163(defun sigio-handler (signal code scp)
164  (declare (ignore signal code scp))
165  (mapc #'funcall (mapcar #'cdr *sigio-handlers*)))
166
167(defun fcntl (fd command arg)
168  "fcntl(2) - manipulate a file descriptor."
169  (multiple-value-bind (ok error) (unix:unix-fcntl fd command arg)
170    (cond (ok)
171          (t (error "fcntl: ~A" (unix:get-unix-error-msg error))))))
172
173(defimplementation add-sigio-handler (socket fn)
174  (set-sigio-handler)
175  (let ((fd (socket-fd socket)))
176    (fcntl fd unix:f-setown (unix:unix-getpid))
177    (let ((old-flags (fcntl fd unix:f-getfl 0)))
178      (fcntl fd unix:f-setfl (logior old-flags unix:fasync)))
179    (assert (not (assoc fd *sigio-handlers*)))
180    (push (cons fd fn) *sigio-handlers*)))
181
182(defimplementation remove-sigio-handlers (socket)
183  (let ((fd (socket-fd socket)))
184    (when (assoc fd *sigio-handlers*)
185      (setf *sigio-handlers* (remove fd *sigio-handlers* :key #'car))
186      (let ((old-flags (fcntl fd unix:f-getfl 0)))
187        (fcntl fd unix:f-setfl (logandc2 old-flags unix:fasync)))
188      (sys:invalidate-descriptor fd))
189    (assert (not (assoc fd *sigio-handlers*)))
190    (when (null *sigio-handlers*)
191      (sys:default-interrupt :sigio))))
192
193;;;;; SERVE-EVENT
194
195(defimplementation add-fd-handler (socket fn)
196  (let ((fd (socket-fd socket)))
197    (sys:add-fd-handler fd :input (lambda (_) _ (funcall fn)))))
198
199(defimplementation remove-fd-handlers (socket)
200  (sys:invalidate-descriptor (socket-fd socket)))
201
202(defimplementation wait-for-input (streams &optional timeout)
203  (assert (member timeout '(nil t)))
204  (loop
205   (let ((ready (remove-if-not #'listen streams)))
206     (when ready (return ready)))
207   (when timeout (return nil))
208   (multiple-value-bind (in out) (make-pipe)
209     (let* ((f (constantly t))
210            (handlers (loop for s in (cons in (mapcar #'to-fd-stream streams))
211                            collect (add-one-shot-handler s f))))
212       (unwind-protect
213            (let ((*interrupt-queued-handler* (lambda ()
214                                                (write-char #\! out))))
215              (when (check-slime-interrupts) (return :interrupt))
216              (sys:serve-event))
217         (mapc #'sys:remove-fd-handler handlers)
218         (close in)
219         (close out))))))
220
221(defun to-fd-stream (stream)
222  (etypecase stream
223    (sys:fd-stream stream)
224    (synonym-stream
225     (to-fd-stream
226      (symbol-value (synonym-stream-symbol stream))))
227    (two-way-stream
228     (to-fd-stream (two-way-stream-input-stream stream)))))
229
230(defun add-one-shot-handler (stream function)
231  (let (handler)
232    (setq handler (sys:add-fd-handler (sys:fd-stream-fd stream) :input
233                                      (lambda (fd)
234                                        (declare (ignore fd))
235                                        (sys:remove-fd-handler handler)
236                                        (funcall function stream))))))
237
238(defun make-pipe ()
239  (multiple-value-bind (in out) (unix:unix-pipe)
240    (values (sys:make-fd-stream in :input t :buffering :none)
241            (sys:make-fd-stream out :output t :buffering :none))))
242
243
244;;;; Stream handling
245
246(defimplementation gray-package-name ()
247  "EXT")
248
249
250;;;; Compilation Commands
251
252(defvar *previous-compiler-condition* nil
253  "Used to detect duplicates.")
254
255(defvar *previous-context* nil
256  "Previous compiler error context.")
257
258(defvar *buffer-name* nil
259  "The name of the Emacs buffer we are compiling from.
260NIL if we aren't compiling from a buffer.")
261
262(defvar *buffer-start-position* nil)
263(defvar *buffer-substring* nil)
264
265(defimplementation call-with-compilation-hooks (function)
266  (let ((*previous-compiler-condition* nil)
267        (*previous-context* nil)
268        (*print-readably* nil))
269    (handler-bind ((c::compiler-error #'handle-notification-condition)
270                   (c::style-warning  #'handle-notification-condition)
271                   (c::warning        #'handle-notification-condition))
272      (funcall function))))
273
274(defimplementation swank-compile-file (input-file output-file
275                                       load-p external-format
276                                       &key policy)
277  (declare (ignore policy))
278  (clear-xref-info input-file)
279  (with-compilation-hooks ()
280    (let ((*buffer-name* nil)
281          (ext:*ignore-extra-close-parentheses* nil))
282      (multiple-value-bind (output-file warnings-p failure-p)
283          (compile-file input-file :output-file output-file
284                        :external-format external-format)
285        (values output-file warnings-p
286                (or failure-p
287                    (when load-p
288                      ;; Cache the latest source file for definition-finding.
289                      (source-cache-get input-file
290                                        (file-write-date input-file))
291                      (not (load output-file)))))))))
292
293(defimplementation swank-compile-string (string &key buffer position filename
294                                                line column policy)
295  (declare (ignore filename line column policy))
296  (with-compilation-hooks ()
297    (let ((*buffer-name* buffer)
298          (*buffer-start-position* position)
299          (*buffer-substring* string)
300          (source-info (list :emacs-buffer buffer
301                             :emacs-buffer-offset position
302                             :emacs-buffer-string string)))
303      (with-input-from-string (stream string)
304        (let ((failurep (ext:compile-from-stream stream :source-info
305                                                source-info)))
306          (not failurep))))))
307
308
309;;;;; Trapping notes
310;;;
311;;; We intercept conditions from the compiler and resignal them as
312;;; `SWANK:COMPILER-CONDITION's.
313
314(defun handle-notification-condition (condition)
315  "Handle a condition caused by a compiler warning."
316  (unless (eq condition *previous-compiler-condition*)
317    (let ((context (c::find-error-context nil)))
318      (setq *previous-compiler-condition* condition)
319      (setq *previous-context* context)
320      (signal-compiler-condition condition context))))
321
322(defun signal-compiler-condition (condition context)
323  (signal 'compiler-condition
324          :original-condition condition
325          :severity (severity-for-emacs condition)
326          :message (compiler-condition-message condition)
327          :source-context (compiler-error-context context)
328          :location (if (read-error-p condition)
329                        (read-error-location condition)
330                        (compiler-note-location context))))
331
332(defun severity-for-emacs (condition)
333  "Return the severity of CONDITION."
334  (etypecase condition
335    ((satisfies read-error-p) :read-error)
336    (c::compiler-error :error)
337    (c::style-warning :note)
338    (c::warning :warning)))
339
340(defun read-error-p (condition)
341  (eq (type-of condition) 'c::compiler-read-error))
342
343(defun compiler-condition-message (condition)
344  "Briefly describe a compiler error for Emacs.
345When Emacs presents the message it already has the source popped up
346and the source form highlighted. This makes much of the information in
347the error-context redundant."
348  (princ-to-string condition))
349
350(defun compiler-error-context (error-context)
351  "Describe context information for Emacs."
352  (declare (type (or c::compiler-error-context null) error-context))
353  (multiple-value-bind (enclosing source)
354      (if error-context
355          (values (c::compiler-error-context-enclosing-source error-context)
356                  (c::compiler-error-context-source error-context)))
357    (if (or enclosing source)
358        (format nil "~@[--> ~{~<~%--> ~1:;~A ~>~}~%~]~
359                     ~@[==>~{~&~A~}~]"
360                enclosing source))))
361
362(defun read-error-location (condition)
363  (let* ((finfo (car (c::source-info-current-file c::*source-info*)))
364         (file (c::file-info-name finfo))
365         (pos (c::compiler-read-error-position condition)))
366    (cond ((and (eq file :stream) *buffer-name*)
367           (make-location (list :buffer *buffer-name*)
368                          (list :offset *buffer-start-position* pos)))
369          ((and (pathnamep file) (not *buffer-name*))
370           (make-location (list :file (unix-truename file))
371                          (list :position (1+ pos))))
372          (t (break)))))
373
374(defun compiler-note-location (context)
375  "Derive the location of a complier message from its context.
376Return a `location' record, or (:error REASON) on failure."
377  (if (null context)
378      (note-error-location)
379      (with-struct (c::compiler-error-context- file-name
380                                               original-source
381                                               original-source-path) context
382        (or (locate-compiler-note file-name original-source
383                                  (reverse original-source-path))
384            (note-error-location)))))
385
386(defun note-error-location ()
387  "Pseudo-location for notes that can't be located."
388  (cond (*compile-file-truename*
389         (make-location (list :file (unix-truename *compile-file-truename*))
390                        (list :eof)))
391        (*buffer-name*
392         (make-location (list :buffer *buffer-name*)
393                        (list :position *buffer-start-position*)))
394        (t (list :error "No error location available."))))
395
396(defun locate-compiler-note (file source source-path)
397  (cond ((and (eq file :stream) *buffer-name*)
398         ;; Compiling from a buffer
399         (make-location (list :buffer *buffer-name*)
400                        (list :offset *buffer-start-position*
401                              (source-path-string-position
402                               source-path *buffer-substring*))))
403        ((and (pathnamep file) (null *buffer-name*))
404         ;; Compiling from a file
405         (make-location (list :file (unix-truename file))
406                        (list :position (1+ (source-path-file-position
407                                             source-path file)))))
408        ((and (eq file :lisp) (stringp source))
409         ;; No location known, but we have the source form.
410         ;; XXX How is this case triggered?  -luke (16/May/2004)
411         ;; This can happen if the compiler needs to expand a macro
412         ;; but the macro-expander is not yet compiled.  Calling the
413         ;; (interpreted) macro-expander triggers IR1 conversion of
414         ;; the lambda expression for the expander and invokes the
415         ;; compiler recursively.
416         (make-location (list :source-form source)
417                        (list :position 1)))))
418
419(defun unix-truename (pathname)
420  (ext:unix-namestring (truename pathname)))
421
422
423;;;; XREF
424;;;
425;;; Cross-reference support is based on the standard CMUCL `XREF'
426;;; package. This package has some caveats: XREF information is
427;;; recorded during compilation and not preserved in fasl files, and
428;;; XREF recording is disabled by default. Redefining functions can
429;;; also cause duplicate references to accumulate, but
430;;; `swank-compile-file' will automatically clear out any old records
431;;; from the same filename.
432;;;
433;;; To enable XREF recording, set `c:*record-xref-info*' to true. To
434;;; clear out the XREF database call `xref:init-xref-database'.
435
436(defmacro defxref (name function)
437  `(defimplementation ,name (name)
438    (xref-results (,function name))))
439
440(defxref who-calls      xref:who-calls)
441(defxref who-references xref:who-references)
442(defxref who-binds      xref:who-binds)
443(defxref who-sets       xref:who-sets)
444
445;;; More types of XREF information were added since 18e:
446;;;
447
448(defxref who-macroexpands xref:who-macroexpands)
449;; XXX
450(defimplementation who-specializes (symbol)
451  (let* ((methods (xref::who-specializes (find-class symbol)))
452         (locations (mapcar #'method-location methods)))
453    (mapcar #'list methods locations)))
454
455(defun xref-results (contexts)
456  (mapcar (lambda (xref)
457            (list (xref:xref-context-name xref)
458                  (resolve-xref-location xref)))
459          contexts))
460
461(defun resolve-xref-location (xref)
462  (let ((name (xref:xref-context-name xref))
463        (file (xref:xref-context-file xref))
464        (source-path (xref:xref-context-source-path xref)))
465    (cond ((and file source-path)
466           (let ((position (source-path-file-position source-path file)))
467             (make-location (list :file (unix-truename file))
468                            (list :position (1+ position)))))
469          (file
470           (make-location (list :file (unix-truename file))
471                          (list :function-name (string name))))
472          (t
473           `(:error ,(format nil "Unknown source location: ~S ~S ~S "
474                             name file source-path))))))
475
476(defun clear-xref-info (namestring)
477  "Clear XREF notes pertaining to NAMESTRING.
478This is a workaround for a CMUCL bug: XREF records are cumulative."
479  (when c:*record-xref-info*
480    (let ((filename (truename namestring)))
481      (dolist (db (list xref::*who-calls*
482                        xref::*who-is-called*
483                        xref::*who-macroexpands*
484                        xref::*who-references*
485                        xref::*who-binds*
486                        xref::*who-sets*))
487        (maphash (lambda (target contexts)
488                   ;; XXX update during traversal?
489                   (setf (gethash target db)
490                         (delete filename contexts
491                                 :key #'xref:xref-context-file
492                                 :test #'equalp)))
493                 db)))))
494
495
496;;;; Find callers and callees
497;;;
498;;; Find callers and callees by looking at the constant pool of
499;;; compiled code objects.  We assume every fdefn object in the
500;;; constant pool corresponds to a call to that function.  A better
501;;; strategy would be to use the disassembler to find actual
502;;; call-sites.
503
504(labels ((make-stack () (make-array 100 :fill-pointer 0 :adjustable t))
505         (map-cpool (code fun)
506           (declare (type kernel:code-component code) (type function fun))
507           (loop for i from vm:code-constants-offset
508                 below (kernel:get-header-data code)
509                 do (funcall fun (kernel:code-header-ref code i))))
510
511         (callees (fun)
512           (let ((callees (make-stack)))
513             (map-cpool (vm::find-code-object fun)
514                        (lambda (o)
515                          (when (kernel:fdefn-p o)
516                            (vector-push-extend (kernel:fdefn-function o)
517                                                callees))))
518             (coerce callees 'list)))
519
520         (callers (fun)
521           (declare (function fun))
522           (let ((callers (make-stack)))
523             (ext:gc :full t)
524             ;; scan :dynamic first to avoid the need for even more gcing
525             (dolist (space '(:dynamic :read-only :static))
526               (vm::map-allocated-objects
527                (lambda (obj header size)
528                  (declare (type fixnum header) (ignore size))
529                  (when (= vm:code-header-type header)
530                    (map-cpool obj
531                               (lambda (c)
532                                 (when (and (kernel:fdefn-p c)
533                                            (eq (kernel:fdefn-function c) fun))
534                                   (vector-push-extend obj callers))))))
535                space)
536               (ext:gc))
537             (coerce callers 'list)))
538
539         (entry-points (code)
540           (loop for entry = (kernel:%code-entry-points code)
541                 then (kernel::%function-next entry)
542                 while entry
543                 collect entry))
544
545         (guess-main-entry-point (entry-points)
546           (or (find-if (lambda (fun)
547                          (ext:valid-function-name-p
548                           (kernel:%function-name fun)))
549                        entry-points)
550               (car entry-points)))
551
552         (fun-dspec (fun)
553           (list (kernel:%function-name fun) (function-location fun)))
554
555         (code-dspec (code)
556           (let ((eps (entry-points code))
557                 (di (kernel:%code-debug-info code)))
558             (cond (eps (fun-dspec (guess-main-entry-point eps)))
559                   (di (list (c::debug-info-name di)
560                             (debug-info-function-name-location di)))
561                   (t (list (princ-to-string code)
562                            `(:error "No src-loc available")))))))
563  (declare (inline map-cpool))
564
565  (defimplementation list-callers (symbol)
566    (mapcar #'code-dspec (callers (coerce symbol 'function) )))
567
568  (defimplementation list-callees (symbol)
569    (mapcar #'fun-dspec (callees symbol))))
570
571(defun test-list-callers (count)
572  (let ((funsyms '()))
573    (do-all-symbols (s)
574      (when (and (fboundp s)
575                 (functionp (symbol-function s))
576                 (not (macro-function s))
577                 (not (special-operator-p s)))
578        (push s funsyms)))
579    (let ((len (length funsyms)))
580      (dotimes (i count)
581        (let ((sym (nth (random len) funsyms)))
582          (format t "~s -> ~a~%" sym (mapcar #'car (list-callers sym))))))))
583
584;; (test-list-callers 100)
585
586
587;;;; Resolving source locations
588;;;
589;;; Our mission here is to "resolve" references to code locations into
590;;; actual file/buffer names and character positions. The references
591;;; we work from come out of the compiler's statically-generated debug
592;;; information, such as `code-location''s and `debug-source''s. For
593;;; more details, see the "Debugger Programmer's Interface" section of
594;;; the CMUCL manual.
595;;;
596;;; The first step is usually to find the corresponding "source-path"
597;;; for the location. Once we have the source-path we can pull up the
598;;; source file and `READ' our way through to the right position. The
599;;; main source-code groveling work is done in
600;;; `source-path-parser.lisp'.
601
602(defvar *debug-definition-finding* nil
603  "When true don't handle errors while looking for definitions.
604This is useful when debugging the definition-finding code.")
605
606(defmacro safe-definition-finding (&body body)
607  "Execute BODY and return the source-location it returns.
608If an error occurs and `*debug-definition-finding*' is false, then
609return an error pseudo-location.
610
611The second return value is NIL if no error occurs, otherwise it is the
612condition object."
613  `(flet ((body () ,@body))
614    (if *debug-definition-finding*
615        (body)
616        (handler-case (values (progn ,@body) nil)
617          (error (c) (values `(:error ,(trim-whitespace (princ-to-string c)))
618                             c))))))
619
620(defun trim-whitespace (string)
621  (string-trim #(#\newline #\space #\tab) string))
622
623(defun code-location-source-location (code-location)
624  "Safe wrapper around `code-location-from-source-location'."
625  (safe-definition-finding
626   (source-location-from-code-location code-location)))
627
628(defun source-location-from-code-location (code-location)
629  "Return the source location for CODE-LOCATION."
630  (let ((debug-fun (di:code-location-debug-function code-location)))
631    (when (di::bogus-debug-function-p debug-fun)
632      ;; Those lousy cheapskates! They've put in a bogus debug source
633      ;; because the code was compiled at a low debug setting.
634      (error "Bogus debug function: ~A" debug-fun)))
635  (let* ((debug-source (di:code-location-debug-source code-location))
636         (from (di:debug-source-from debug-source))
637         (name (di:debug-source-name debug-source)))
638    (ecase from
639      (:file
640       (location-in-file name code-location debug-source))
641      (:stream
642       (location-in-stream code-location debug-source))
643      (:lisp
644       ;; The location comes from a form passed to `compile'.
645       ;; The best we can do is return the form itself for printing.
646       (make-location
647        (list :source-form (with-output-to-string (*standard-output*)
648                             (debug::print-code-location-source-form
649                              code-location 100 t)))
650        (list :position 1))))))
651
652(defun location-in-file (filename code-location debug-source)
653  "Resolve the source location for CODE-LOCATION in FILENAME."
654  (let* ((code-date (di:debug-source-created debug-source))
655         (root-number (di:debug-source-root-number debug-source))
656         (source-code (get-source-code filename code-date)))
657    (with-input-from-string (s source-code)
658      (make-location (list :file (unix-truename filename))
659                     (list :position (1+ (code-location-stream-position
660                                          code-location s root-number)))
661                     `(:snippet ,(read-snippet s))))))
662
663(defun location-in-stream (code-location debug-source)
664  "Resolve the source location for a CODE-LOCATION from a stream.
665This only succeeds if the code was compiled from an Emacs buffer."
666  (unless (debug-source-info-from-emacs-buffer-p debug-source)
667    (error "The code is compiled from a non-SLIME stream."))
668  (let* ((info (c::debug-source-info debug-source))
669         (string (getf info :emacs-buffer-string))
670         (position (code-location-string-offset
671                    code-location
672                    string)))
673    (make-location
674     (list :buffer (getf info :emacs-buffer))
675     (list :offset (getf info :emacs-buffer-offset) position)
676     (list :snippet (with-input-from-string (s string)
677                      (file-position s position)
678                      (read-snippet s))))))
679
680;;;;; Function-name locations
681;;;
682(defun debug-info-function-name-location (debug-info)
683  "Return a function-name source-location for DEBUG-INFO.
684Function-name source-locations are a fallback for when precise
685positions aren't available."
686  (with-struct (c::debug-info- (fname name) source) debug-info
687    (with-struct (c::debug-source- info from name) (car source)
688      (ecase from
689        (:file
690         (make-location (list :file (namestring (truename name)))
691                        (list :function-name (string fname))))
692        (:stream
693         (assert (debug-source-info-from-emacs-buffer-p (car source)))
694         (make-location (list :buffer (getf info :emacs-buffer))
695                        (list :function-name (string fname))))
696        (:lisp
697         (make-location (list :source-form (princ-to-string (aref name 0)))
698                        (list :position 1)))))))
699
700(defun debug-source-info-from-emacs-buffer-p (debug-source)
701  "Does the `info' slot of DEBUG-SOURCE contain an Emacs buffer location?
702This is true for functions that were compiled directly from buffers."
703  (info-from-emacs-buffer-p (c::debug-source-info debug-source)))
704
705(defun info-from-emacs-buffer-p (info)
706  (and info
707       (consp info)
708       (eq :emacs-buffer (car info))))
709
710
711;;;;; Groveling source-code for positions
712
713(defun code-location-stream-position (code-location stream root)
714  "Return the byte offset of CODE-LOCATION in STREAM.  Extract the
715toplevel-form-number and form-number from CODE-LOCATION and use that
716to find the position of the corresponding form.
717
718Finish with STREAM positioned at the start of the code location."
719  (let* ((location (debug::maybe-block-start-location code-location))
720         (tlf-offset (- (di:code-location-top-level-form-offset location)
721                        root))
722         (form-number (di:code-location-form-number location)))
723    (let ((pos (form-number-stream-position tlf-offset form-number stream)))
724      (file-position stream pos)
725      pos)))
726
727(defun form-number-stream-position (tlf-number form-number stream)
728  "Return the starting character position of a form in STREAM.
729TLF-NUMBER is the top-level-form number.
730FORM-NUMBER is an index into a source-path table for the TLF."
731  (multiple-value-bind (tlf position-map) (read-source-form tlf-number stream)
732    (let* ((path-table (di:form-number-translations tlf 0))
733           (source-path
734            (if (<= (length path-table) form-number) ; source out of sync?
735                (list 0)                ; should probably signal a condition
736                (reverse (cdr (aref path-table form-number))))))
737      (source-path-source-position source-path tlf position-map))))
738
739(defun code-location-string-offset (code-location string)
740  "Return the byte offset of CODE-LOCATION in STRING.
741See CODE-LOCATION-STREAM-POSITION."
742  (with-input-from-string (s string)
743    (code-location-stream-position code-location s 0)))
744
745
746;;;; Finding definitions
747
748;;; There are a great many different types of definition for us to
749;;; find. We search for definitions of every kind and return them in a
750;;; list.
751
752(defimplementation find-definitions (name)
753  (append (function-definitions name)
754          (setf-definitions name)
755          (variable-definitions name)
756          (class-definitions name)
757          (type-definitions name)
758          (compiler-macro-definitions name)
759          (source-transform-definitions name)
760          (function-info-definitions name)
761          (ir1-translator-definitions name)
762          (template-definitions name)
763          (primitive-definitions name)
764          (vm-support-routine-definitions name)
765          ))
766
767;;;;; Functions, macros, generic functions, methods
768;;;
769;;; We make extensive use of the compile-time debug information that
770;;; CMUCL records, in particular "debug functions" and "code
771;;; locations." Refer to the "Debugger Programmer's Interface" section
772;;; of the CMUCL manual for more details.
773
774(defun function-definitions (name)
775  "Return definitions for NAME in the \"function namespace\", i.e.,
776regular functions, generic functions, methods and macros.
777NAME can any valid function name (e.g, (setf car))."
778  (let ((macro?    (and (symbolp name) (macro-function name)))
779        (function? (and (ext:valid-function-name-p name)
780                        (ext:info :function :definition name)
781                        (if (symbolp name) (fboundp name) t))))
782    (cond (macro?
783           (list `((defmacro ,name)
784                   ,(function-location (macro-function name)))))
785          (function?
786           (let ((function (fdefinition name)))
787             (if (genericp function)
788                 (gf-definitions name function)
789                 (list (list `(function ,name)
790                             (function-location function)))))))))
791
792;;;;;; Ordinary (non-generic/macro/special) functions
793;;;
794;;; First we test if FUNCTION is a closure created by defstruct, and
795;;; if so extract the defstruct-description (`dd') from the closure
796;;; and find the constructor for the struct.  Defstruct creates a
797;;; defun for the default constructor and we use that as an
798;;; approximation to the source location of the defstruct.
799;;;
800;;; For an ordinary function we return the source location of the
801;;; first code-location we find.
802;;;
803(defun function-location (function)
804  "Return the source location for FUNCTION."
805  (cond ((struct-closure-p function)
806         (struct-closure-location function))
807        ((c::byte-function-or-closure-p function)
808         (byte-function-location function))
809        (t
810         (compiled-function-location function))))
811
812(defun compiled-function-location (function)
813  "Return the location of a regular compiled function."
814  (multiple-value-bind (code-location error)
815      (safe-definition-finding (function-first-code-location function))
816    (cond (error (list :error (princ-to-string error)))
817          (t (code-location-source-location code-location)))))
818
819(defun function-first-code-location (function)
820  "Return the first code-location we can find for FUNCTION."
821  (and (function-has-debug-function-p function)
822       (di:debug-function-start-location
823        (di:function-debug-function function))))
824
825(defun function-has-debug-function-p (function)
826  (di:function-debug-function function))
827
828(defun function-code-object= (closure function)
829  (and (eq (vm::find-code-object closure)
830           (vm::find-code-object function))
831       (not (eq closure function))))
832
833(defun byte-function-location (fun)
834  "Return the location of the byte-compiled function FUN."
835  (etypecase fun
836    ((or c::hairy-byte-function c::simple-byte-function)
837     (let* ((di (kernel:%code-debug-info (c::byte-function-component fun))))
838       (if di
839           (debug-info-function-name-location di)
840           `(:error
841             ,(format nil "Byte-function without debug-info: ~a" fun)))))
842    (c::byte-closure
843     (byte-function-location (c::byte-closure-function fun)))))
844
845;;; Here we deal with structure accessors. Note that `dd' is a
846;;; "defstruct descriptor" structure in CMUCL. A `dd' describes a
847;;; `defstruct''d structure.
848
849(defun struct-closure-p (function)
850  "Is FUNCTION a closure created by defstruct?"
851  (or (function-code-object= function #'kernel::structure-slot-accessor)
852      (function-code-object= function #'kernel::structure-slot-setter)
853      (function-code-object= function #'kernel::%defstruct)))
854
855(defun struct-closure-location (function)
856  "Return the location of the structure that FUNCTION belongs to."
857  (assert (struct-closure-p function))
858  (safe-definition-finding
859    (dd-location (struct-closure-dd function))))
860
861(defun struct-closure-dd (function)
862  "Return the defstruct-definition (dd) of FUNCTION."
863  (assert (= (kernel:get-type function) vm:closure-header-type))
864  (flet ((find-layout (function)
865           (sys:find-if-in-closure
866            (lambda (x)
867              (let ((value (if (di::indirect-value-cell-p x)
868                               (c:value-cell-ref x)
869                               x)))
870		(when (kernel::layout-p value)
871                  (return-from find-layout value))))
872            function)))
873    (kernel:layout-info (find-layout function))))
874
875(defun dd-location (dd)
876  "Return the location of a `defstruct'."
877  (let ((ctor (struct-constructor dd)))
878    (cond (ctor
879           (function-location (coerce ctor 'function)))
880          (t
881           (let ((name (kernel:dd-name dd)))
882             (multiple-value-bind (location foundp)
883                 (ext:info :source-location :defvar name)
884               (cond (foundp
885                      (resolve-source-location location))
886                     (t
887                      (error "No location for defstruct: ~S" name)))))))))
888
889(defun struct-constructor (dd)
890  "Return the name of the constructor from a defstruct definition."
891  (let* ((constructor (or (kernel:dd-default-constructor dd)
892                          (car (kernel::dd-constructors dd)))))
893    (if (consp constructor) (car constructor) constructor)))
894
895;;;;;; Generic functions and methods
896
897(defun gf-definitions (name function)
898  "Return the definitions of a generic function and its methods."
899  (cons (list `(defgeneric ,name) (gf-location function))
900        (gf-method-definitions function)))
901
902(defun gf-location (gf)
903  "Return the location of the generic function GF."
904  (definition-source-location gf (pcl::generic-function-name gf)))
905
906(defun gf-method-definitions (gf)
907  "Return the locations of all methods of the generic function GF."
908  (mapcar #'method-definition (pcl::generic-function-methods gf)))
909
910(defun method-definition (method)
911  (list (method-dspec method)
912        (method-location method)))
913
914(defun method-dspec (method)
915  "Return a human-readable \"definition specifier\" for METHOD."
916  (let* ((gf (pcl:method-generic-function method))
917         (name (pcl:generic-function-name gf))
918         (specializers (pcl:method-specializers method))
919         (qualifiers (pcl:method-qualifiers method)))
920    `(method ,name ,@qualifiers ,(pcl::unparse-specializers specializers))))
921
922(defun method-location (method)
923  (typecase method
924    (pcl::standard-accessor-method
925     (definition-source-location
926         (cond ((pcl::definition-source method)
927                method)
928               (t
929                (pcl::slot-definition-class
930                 (pcl::accessor-method-slot-definition method))))
931         (pcl::accessor-method-slot-name method)))
932    (t
933     (function-location (or (pcl::method-fast-function method)
934                            (pcl:method-function method))))))
935
936(defun genericp (fn)
937  (typep fn 'generic-function))
938
939;;;;;; Types and classes
940
941(defun type-definitions (name)
942  "Return `deftype' locations for type NAME."
943  (maybe-make-definition (ext:info :type :expander name) 'deftype name))
944
945(defun maybe-make-definition (function kind name)
946  "If FUNCTION is non-nil then return its definition location."
947  (if function
948      (list (list `(,kind ,name) (function-location function)))))
949
950(defun class-definitions (name)
951  "Return the definition locations for the class called NAME."
952  (if (symbolp name)
953      (let ((class (kernel::find-class name nil)))
954        (etypecase class
955          (null '())
956          (kernel::structure-class
957           (list (list `(defstruct ,name) (dd-location (find-dd name)))))
958          #+(or)
959          (conditions::condition-class
960           (list (list `(define-condition ,name)
961                       (condition-class-location class))))
962          (kernel::standard-class
963           (list (list `(defclass ,name)
964                       (pcl-class-location (find-class name)))))
965          ((or kernel::built-in-class
966               conditions::condition-class
967               kernel:funcallable-structure-class)
968           (list (list `(class ,name) (class-location class))))))))
969
970(defun pcl-class-location (class)
971  "Return the `defclass' location for CLASS."
972  (definition-source-location class (pcl:class-name class)))
973
974;; FIXME: eval used for backward compatibility.
975(defun class-location (class)
976  (declare (type kernel::class class))
977  (let ((name (kernel:%class-name class)))
978    (multiple-value-bind (loc found?)
979        (let ((x (ignore-errors
980                   (multiple-value-list
981                    (eval `(ext:info :source-location :class ',name))))))
982          (values-list x))
983      (cond (found? (resolve-source-location loc))
984            (`(:error
985               ,(format nil "No location recorded for class: ~S" name)))))))
986
987(defun find-dd (name)
988  "Find the defstruct-definition by the name of its structure-class."
989  (let ((layout (ext:info :type :compiler-layout name)))
990    (if layout
991        (kernel:layout-info layout))))
992
993(defun condition-class-location (class)
994  (let ((slots (conditions::condition-class-slots class))
995        (name (conditions::condition-class-name class)))
996    (cond ((null slots)
997           `(:error ,(format nil "No location info for condition: ~A" name)))
998          (t
999           ;; Find the class via one of its slot-reader methods.
1000           (let* ((slot (first slots))
1001                  (gf (fdefinition
1002                       (first (conditions::condition-slot-readers slot)))))
1003             (method-location
1004              (first
1005               (pcl:compute-applicable-methods-using-classes
1006                gf (list (find-class name))))))))))
1007
1008(defun make-name-in-file-location (file string)
1009  (multiple-value-bind (filename c)
1010      (ignore-errors
1011        (unix-truename (merge-pathnames (make-pathname :type "lisp")
1012                                        file)))
1013    (cond (filename (make-location `(:file ,filename)
1014                                   `(:function-name ,(string string))))
1015          (t (list :error (princ-to-string c))))))
1016
1017(defun source-location-form-numbers (location)
1018  (c::decode-form-numbers (c::form-numbers-form-numbers location)))
1019
1020(defun source-location-tlf-number (location)
1021  (nth-value 0 (source-location-form-numbers location)))
1022
1023(defun source-location-form-number (location)
1024  (nth-value 1 (source-location-form-numbers location)))
1025
1026(defun resolve-file-source-location (location)
1027  (let ((filename (c::file-source-location-pathname location))
1028        (tlf-number (source-location-tlf-number location))
1029        (form-number (source-location-form-number location)))
1030    (with-open-file (s filename)
1031      (let ((pos (form-number-stream-position tlf-number form-number s)))
1032        (make-location `(:file ,(unix-truename filename))
1033                       `(:position ,(1+ pos)))))))
1034
1035(defun resolve-stream-source-location (location)
1036  (let ((info (c::stream-source-location-user-info location))
1037        (tlf-number (source-location-tlf-number location))
1038        (form-number (source-location-form-number location)))
1039    ;; XXX duplication in frame-source-location
1040    (assert (info-from-emacs-buffer-p info))
1041    (destructuring-bind (&key emacs-buffer emacs-buffer-string
1042                              emacs-buffer-offset) info
1043      (with-input-from-string (s emacs-buffer-string)
1044        (let ((pos (form-number-stream-position tlf-number form-number s)))
1045          (make-location `(:buffer ,emacs-buffer)
1046                         `(:offset ,emacs-buffer-offset ,pos)))))))
1047
1048;; XXX predicates for 18e backward compatibilty.  Remove them when
1049;; we're 19a only.
1050(defun file-source-location-p (object)
1051  (when (fboundp 'c::file-source-location-p)
1052    (c::file-source-location-p object)))
1053
1054(defun stream-source-location-p (object)
1055  (when (fboundp 'c::stream-source-location-p)
1056    (c::stream-source-location-p object)))
1057
1058(defun source-location-p (object)
1059  (or (file-source-location-p object)
1060      (stream-source-location-p object)))
1061
1062(defun resolve-source-location (location)
1063  (etypecase location
1064    ((satisfies file-source-location-p)
1065     (resolve-file-source-location location))
1066    ((satisfies stream-source-location-p)
1067     (resolve-stream-source-location location))))
1068
1069(defun definition-source-location (object name)
1070  (let ((source (pcl::definition-source object)))
1071    (etypecase source
1072      (null
1073       `(:error ,(format nil "No source info for: ~A" object)))
1074      ((satisfies source-location-p)
1075       (resolve-source-location source))
1076      (pathname
1077       (make-name-in-file-location source name))
1078      (cons
1079       (destructuring-bind ((dg name) pathname) source
1080         (declare (ignore dg))
1081         (etypecase pathname
1082           (pathname (make-name-in-file-location pathname (string name)))
1083           (null `(:error ,(format nil "Cannot resolve: ~S" source)))))))))
1084
1085(defun setf-definitions (name)
1086  (let ((f (or (ext:info :setf :inverse name)
1087               (ext:info :setf :expander name)
1088               (and (symbolp name)
1089                    (fboundp `(setf ,name))
1090                    (fdefinition `(setf ,name))))))
1091    (if f
1092        `(((setf ,name) ,(function-location (cond ((functionp  f) f)
1093                                                  ((macro-function f))
1094                                                  ((fdefinition f)))))))))
1095
1096(defun variable-location (symbol)
1097  (multiple-value-bind (location foundp)
1098      ;; XXX for 18e compatibilty. rewrite this when we drop 18e
1099      ;; support.
1100      (ignore-errors (eval `(ext:info :source-location :defvar ',symbol)))
1101    (if (and foundp location)
1102        (resolve-source-location location)
1103        `(:error ,(format nil "No source info for variable ~S" symbol)))))
1104
1105(defun variable-definitions (name)
1106  (if (symbolp name)
1107      (multiple-value-bind (kind recorded-p) (ext:info :variable :kind name)
1108        (if recorded-p
1109            (list (list `(variable ,kind ,name)
1110                        (variable-location name)))))))
1111
1112(defun compiler-macro-definitions (symbol)
1113  (maybe-make-definition (compiler-macro-function symbol)
1114                         'define-compiler-macro
1115                         symbol))
1116
1117(defun source-transform-definitions (name)
1118  (maybe-make-definition (ext:info :function :source-transform name)
1119                         'c:def-source-transform
1120                         name))
1121
1122(defun function-info-definitions (name)
1123  (let ((info (ext:info :function :info name)))
1124    (if info
1125        (append (loop for transform in (c::function-info-transforms info)
1126                      collect (list `(c:deftransform ,name
1127                                      ,(c::type-specifier
1128                                        (c::transform-type transform)))
1129                                    (function-location (c::transform-function
1130                                                        transform))))
1131                (maybe-make-definition (c::function-info-derive-type info)
1132                                       'c::derive-type name)
1133                (maybe-make-definition (c::function-info-optimizer info)
1134                                       'c::optimizer name)
1135                (maybe-make-definition (c::function-info-ltn-annotate info)
1136                                       'c::ltn-annotate name)
1137                (maybe-make-definition (c::function-info-ir2-convert info)
1138                                       'c::ir2-convert name)
1139                (loop for template in (c::function-info-templates info)
1140                      collect (list `(,(type-of template)
1141                                       ,(c::template-name template))
1142                                    (function-location
1143                                     (c::vop-info-generator-function
1144                                      template))))))))
1145
1146(defun ir1-translator-definitions (name)
1147  (maybe-make-definition (ext:info :function :ir1-convert name)
1148                         'c:def-ir1-translator name))
1149
1150(defun template-definitions (name)
1151  (let* ((templates (c::backend-template-names c::*backend*))
1152         (template (gethash name templates)))
1153    (etypecase template
1154      (null)
1155      (c::vop-info
1156       (maybe-make-definition (c::vop-info-generator-function template)
1157                              (type-of template) name)))))
1158
1159;; for cases like: (%primitive NAME ...)
1160(defun primitive-definitions (name)
1161  (let ((csym (find-symbol (string name) 'c)))
1162    (and csym
1163         (not (eq csym name))
1164         (template-definitions csym))))
1165
1166(defun vm-support-routine-definitions (name)
1167  (let ((sr (c::backend-support-routines c::*backend*))
1168        (name (find-symbol (string name) 'c)))
1169    (and name
1170         (slot-exists-p sr name)
1171         (maybe-make-definition (slot-value sr name)
1172                                (find-symbol (string 'vm-support-routine) 'c)
1173                                name))))
1174
1175
1176;;;; Documentation.
1177
1178(defimplementation describe-symbol-for-emacs (symbol)
1179  (let ((result '()))
1180    (flet ((doc (kind)
1181             (or (documentation symbol kind) :not-documented))
1182           (maybe-push (property value)
1183             (when value
1184               (setf result (list* property value result)))))
1185      (maybe-push
1186       :variable (multiple-value-bind (kind recorded-p)
1187                     (ext:info variable kind symbol)
1188                   (declare (ignore kind))
1189                   (if (or (boundp symbol) recorded-p)
1190                       (doc 'variable))))
1191      (when (fboundp symbol)
1192	(maybe-push
1193         (cond ((macro-function symbol)     :macro)
1194               ((special-operator-p symbol) :special-operator)
1195               ((genericp (fdefinition symbol)) :generic-function)
1196               (t :function))
1197         (doc 'function)))
1198      (maybe-push
1199       :setf (if (or (ext:info setf inverse symbol)
1200                     (ext:info setf expander symbol))
1201                 (doc 'setf)))
1202      (maybe-push
1203       :type (if (ext:info type kind symbol)
1204                 (doc 'type)))
1205      (maybe-push
1206       :class (if (find-class symbol nil)
1207                  (doc 'class)))
1208      (maybe-push
1209       :alien-type (if (not (eq (ext:info alien-type kind symbol) :unknown))
1210                       (doc 'alien-type)))
1211      (maybe-push
1212       :alien-struct (if (ext:info alien-type struct symbol)
1213                         (doc nil)))
1214      (maybe-push
1215       :alien-union (if (ext:info alien-type union symbol)
1216                         (doc nil)))
1217      (maybe-push
1218       :alien-enum (if (ext:info alien-type enum symbol)
1219                       (doc nil)))
1220      result)))
1221
1222(defimplementation describe-definition (symbol namespace)
1223  (describe (ecase namespace
1224              (:variable
1225               symbol)
1226              ((:function :generic-function)
1227               (symbol-function symbol))
1228              (:setf
1229               (or (ext:info setf inverse symbol)
1230                   (ext:info setf expander symbol)))
1231              (:type
1232               (kernel:values-specifier-type symbol))
1233              (:class
1234               (find-class symbol))
1235              (:alien-struct
1236               (ext:info :alien-type :struct symbol))
1237              (:alien-union
1238               (ext:info :alien-type :union symbol))
1239              (:alien-enum
1240               (ext:info :alien-type :enum symbol))
1241              (:alien-type
1242               (ecase (ext:info :alien-type :kind symbol)
1243                 (:primitive
1244                  (let ((alien::*values-type-okay* t))
1245                    (funcall (ext:info :alien-type :translator symbol)
1246                             (list symbol))))
1247                 ((:defined)
1248                  (ext:info :alien-type :definition symbol))
1249                 (:unknown :unkown))))))
1250
1251;;;;; Argument lists
1252
1253(defimplementation arglist (fun)
1254  (etypecase fun
1255    (function (function-arglist fun))
1256    (symbol (function-arglist (or (macro-function fun)
1257                                  (symbol-function fun))))))
1258
1259(defun function-arglist (fun)
1260  (let ((arglist
1261         (cond ((eval:interpreted-function-p fun)
1262                (eval:interpreted-function-arglist fun))
1263               ((pcl::generic-function-p fun)
1264                (pcl:generic-function-lambda-list fun))
1265               ((c::byte-function-or-closure-p fun)
1266                (byte-code-function-arglist fun))
1267               ((kernel:%function-arglist (kernel:%function-self fun))
1268                (handler-case (read-arglist fun)
1269                  (error () :not-available)))
1270               ;; this should work both for compiled-debug-function
1271               ;; and for interpreted-debug-function
1272               (t
1273                (handler-case (debug-function-arglist
1274                               (di::function-debug-function fun))
1275                  (di:unhandled-condition () :not-available))))))
1276    (check-type arglist (or list (member :not-available)))
1277    arglist))
1278
1279(defimplementation function-name (function)
1280  (cond ((eval:interpreted-function-p function)
1281         (eval:interpreted-function-name function))
1282        ((pcl::generic-function-p function)
1283         (pcl::generic-function-name function))
1284        ((c::byte-function-or-closure-p function)
1285         (c::byte-function-name function))
1286        (t (kernel:%function-name (kernel:%function-self function)))))
1287
1288;;; A simple case: the arglist is available as a string that we can
1289;;; `read'.
1290
1291(defun read-arglist (fn)
1292  "Parse the arglist-string of the function object FN."
1293  (let ((string (kernel:%function-arglist
1294                 (kernel:%function-self fn)))
1295        (package (find-package
1296                  (c::compiled-debug-info-package
1297                   (kernel:%code-debug-info
1298                    (vm::find-code-object fn))))))
1299    (with-standard-io-syntax
1300      (let ((*package* (or package *package*)))
1301        (read-from-string string)))))
1302
1303;;; A harder case: an approximate arglist is derived from available
1304;;; debugging information.
1305
1306(defun debug-function-arglist (debug-function)
1307  "Derive the argument list of DEBUG-FUNCTION from debug info."
1308  (let ((args (di::debug-function-lambda-list debug-function))
1309        (required '())
1310        (optional '())
1311        (rest '())
1312        (key '()))
1313    ;; collect the names of debug-vars
1314    (dolist (arg args)
1315      (etypecase arg
1316        (di::debug-variable
1317         (push (di::debug-variable-symbol arg) required))
1318        ((member :deleted)
1319         (push ':deleted required))
1320        (cons
1321         (ecase (car arg)
1322           (:keyword
1323            (push (second arg) key))
1324           (:optional
1325            (push (debug-variable-symbol-or-deleted (second arg)) optional))
1326           (:rest
1327            (push (debug-variable-symbol-or-deleted (second arg)) rest))))))
1328    ;; intersperse lambda keywords as needed
1329    (append (nreverse required)
1330            (if optional (cons '&optional (nreverse optional)))
1331            (if rest (cons '&rest (nreverse rest)))
1332            (if key (cons '&key (nreverse key))))))
1333
1334(defun debug-variable-symbol-or-deleted (var)
1335  (etypecase var
1336    (di:debug-variable
1337     (di::debug-variable-symbol var))
1338    ((member :deleted)
1339     '#:deleted)))
1340
1341(defun symbol-debug-function-arglist (fname)
1342  "Return FNAME's debug-function-arglist and %function-arglist.
1343A utility for debugging DEBUG-FUNCTION-ARGLIST."
1344  (let ((fn (fdefinition fname)))
1345    (values (debug-function-arglist (di::function-debug-function fn))
1346            (kernel:%function-arglist (kernel:%function-self fn)))))
1347
1348;;; Deriving arglists for byte-compiled functions:
1349;;;
1350(defun byte-code-function-arglist (fn)
1351  ;; There doesn't seem to be much arglist information around for
1352  ;; byte-code functions.  Use the arg-count and return something like
1353  ;; (arg0 arg1 ...)
1354  (etypecase fn
1355    (c::simple-byte-function
1356     (loop for i from 0 below (c::simple-byte-function-num-args fn)
1357           collect (make-arg-symbol i)))
1358    (c::hairy-byte-function
1359     (hairy-byte-function-arglist fn))
1360    (c::byte-closure
1361     (byte-code-function-arglist (c::byte-closure-function fn)))))
1362
1363(defun make-arg-symbol (i)
1364  (make-symbol (format nil "~A~D" (string 'arg) i)))
1365
1366;;; A "hairy" byte-function is one that takes a variable number of
1367;;; arguments. `hairy-byte-function' is a type from the bytecode
1368;;; interpreter.
1369;;;
1370(defun hairy-byte-function-arglist (fn)
1371  (let ((counter -1))
1372    (flet ((next-arg () (make-arg-symbol (incf counter))))
1373      (with-struct (c::hairy-byte-function- min-args max-args rest-arg-p
1374                                            keywords-p keywords) fn
1375        (let ((arglist '())
1376              (optional (- max-args min-args)))
1377          ;; XXX isn't there a better way to write this?
1378          ;; (Looks fine to me. -luke)
1379          (dotimes (i min-args)
1380            (push (next-arg) arglist))
1381          (when (plusp optional)
1382            (push '&optional arglist)
1383            (dotimes (i optional)
1384              (push (next-arg) arglist)))
1385          (when rest-arg-p
1386            (push '&rest arglist)
1387            (push (next-arg) arglist))
1388          (when keywords-p
1389            (push '&key arglist)
1390            (loop for (key _ __) in keywords
1391                  do (push key arglist))
1392            (when (eq keywords-p :allow-others)
1393              (push '&allow-other-keys arglist)))
1394          (nreverse arglist))))))
1395
1396
1397;;;; Miscellaneous.
1398
1399(defimplementation macroexpand-all (form &optional env)
1400  (walker:macroexpand-all form env))
1401
1402(defimplementation compiler-macroexpand-1 (form &optional env)
1403  (ext:compiler-macroexpand-1 form env))
1404
1405(defimplementation compiler-macroexpand (form &optional env)
1406  (ext:compiler-macroexpand form env))
1407
1408(defimplementation set-default-directory (directory)
1409  (setf (ext:default-directory) (namestring directory))
1410  ;; Setting *default-pathname-defaults* to an absolute directory
1411  ;; makes the behavior of MERGE-PATHNAMES a bit more intuitive.
1412  (setf *default-pathname-defaults* (pathname (ext:default-directory)))
1413  (default-directory))
1414
1415(defimplementation default-directory ()
1416  (namestring (ext:default-directory)))
1417
1418(defimplementation getpid ()
1419  (unix:unix-getpid))
1420
1421(defimplementation lisp-implementation-type-name ()
1422  "cmucl")
1423
1424(defimplementation quit-lisp ()
1425  (ext::quit))
1426
1427;;; source-path-{stream,file,string,etc}-position moved into
1428;;; source-path-parser
1429
1430
1431;;;; Debugging
1432
1433(defvar *sldb-stack-top*)
1434
1435(defimplementation call-with-debugging-environment (debugger-loop-fn)
1436  (unix:unix-sigsetmask 0)
1437  (let* ((*sldb-stack-top* (or debug:*stack-top-hint* (di:top-frame)))
1438         (debug:*stack-top-hint* nil)
1439         (kernel:*current-level* 0))
1440    (handler-bind ((di::unhandled-condition
1441                    (lambda (condition)
1442                      (error 'sldb-condition
1443                             :original-condition condition))))
1444      (unwind-protect
1445           (progn
1446             #+(or)(sys:scrub-control-stack)
1447             (funcall debugger-loop-fn))
1448        #+(or)(sys:scrub-control-stack)
1449        ))))
1450
1451(defun frame-down (frame)
1452  (handler-case (di:frame-down frame)
1453    (di:no-debug-info () nil)))
1454
1455(defun nth-frame (index)
1456  (do ((frame *sldb-stack-top* (frame-down frame))
1457       (i index (1- i)))
1458      ((zerop i) frame)))
1459
1460(defimplementation compute-backtrace (start end)
1461  (let ((end (or end most-positive-fixnum)))
1462    (loop for f = (nth-frame start) then (frame-down f)
1463          for i from start below end
1464          while f collect f)))
1465
1466(defimplementation print-frame (frame stream)
1467  (let ((*standard-output* stream))
1468    (handler-case
1469        (debug::print-frame-call frame :verbosity 1 :number nil)
1470      (error (e)
1471        (ignore-errors (princ e stream))))))
1472
1473(defimplementation frame-source-location (index)
1474  (let ((frame (nth-frame index)))
1475    (cond ((foreign-frame-p frame) (foreign-frame-source-location frame))
1476          ((code-location-source-location (di:frame-code-location frame))))))
1477
1478(defimplementation eval-in-frame (form index)
1479  (di:eval-in-frame (nth-frame index) form))
1480
1481(defun frame-debug-vars (frame)
1482  "Return a vector of debug-variables in frame."
1483  (let ((loc (di:frame-code-location frame)))
1484    (remove-if
1485     (lambda (v)
1486       (not (eq (di:debug-variable-validity v loc) :valid)))
1487     (di::debug-function-debug-variables (di:frame-debug-function frame)))))
1488
1489(defun debug-var-value (var frame)
1490  (let* ((loc (di:frame-code-location frame))
1491         (validity (di:debug-variable-validity var loc)))
1492    (ecase validity
1493      (:valid (di:debug-variable-value var frame))
1494      ((:invalid :unknown) (make-symbol (string validity))))))
1495
1496(defimplementation frame-locals (index)
1497  (let ((frame (nth-frame index)))
1498    (loop for v across (frame-debug-vars frame)
1499          collect (list :name (di:debug-variable-symbol v)
1500                        :id (di:debug-variable-id v)
1501                        :value (debug-var-value v frame)))))
1502
1503(defimplementation frame-var-value (frame var)
1504  (let* ((frame (nth-frame frame))
1505         (dvar (aref (frame-debug-vars frame) var)))
1506    (debug-var-value dvar frame)))
1507
1508(defimplementation frame-catch-tags (index)
1509  (mapcar #'car (di:frame-catches (nth-frame index))))
1510
1511(defimplementation frame-package (frame-number)
1512  (let* ((frame (nth-frame frame-number))
1513         (dbg-fun (di:frame-debug-function frame)))
1514    (typecase dbg-fun
1515      (di::compiled-debug-function
1516       (let* ((comp (di::compiled-debug-function-component dbg-fun))
1517              (dbg-info (kernel:%code-debug-info comp)))
1518         (typecase dbg-info
1519           (c::compiled-debug-info
1520            (find-package (c::compiled-debug-info-package dbg-info)))))))))
1521
1522(defimplementation return-from-frame (index form)
1523  (let ((sym (find-symbol (string 'find-debug-tag-for-frame)
1524                          :debug-internals)))
1525    (if sym
1526        (let* ((frame (nth-frame index))
1527               (probe (funcall sym frame)))
1528          (cond (probe (throw (car probe) (eval-in-frame form index)))
1529                (t (format nil "Cannot return from frame: ~S" frame))))
1530        "return-from-frame is not implemented in this version of CMUCL.")))
1531
1532(defimplementation activate-stepping (frame)
1533  (set-step-breakpoints (nth-frame frame)))
1534
1535(defimplementation sldb-break-on-return (frame)
1536  (break-on-return (nth-frame frame)))
1537
1538;;; We set the breakpoint in the caller which might be a bit confusing.
1539;;;
1540(defun break-on-return (frame)
1541  (let* ((caller (di:frame-down frame))
1542         (cl (di:frame-code-location caller)))
1543    (flet ((hook (frame bp)
1544             (when (frame-pointer= frame caller)
1545               (di:delete-breakpoint bp)
1546               (signal-breakpoint bp frame))))
1547      (let* ((info (ecase (di:code-location-kind cl)
1548                     ((:single-value-return :unknown-return) nil)
1549                     (:known-return (debug-function-returns
1550                                     (di:frame-debug-function frame)))))
1551             (bp (di:make-breakpoint #'hook cl :kind :code-location
1552                                     :info info)))
1553        (di:activate-breakpoint bp)
1554        `(:ok ,(format nil "Set breakpoint in ~A" caller))))))
1555
1556(defun frame-pointer= (frame1 frame2)
1557  "Return true if the frame pointers of FRAME1 and FRAME2 are the same."
1558  (sys:sap= (di::frame-pointer frame1) (di::frame-pointer frame2)))
1559
1560;;; The PC in escaped frames at a single-return-value point is
1561;;; actually vm:single-value-return-byte-offset bytes after the
1562;;; position given in the debug info.  Here we try to recognize such
1563;;; cases.
1564;;;
1565(defun next-code-locations (frame code-location)
1566  "Like `debug::next-code-locations' but be careful in escaped frames."
1567  (let ((next (debug::next-code-locations code-location)))
1568    (flet ((adjust-pc ()
1569             (let ((cl (di::copy-compiled-code-location code-location)))
1570               (incf (di::compiled-code-location-pc cl)
1571                     vm:single-value-return-byte-offset)
1572               cl)))
1573      (cond ((and (di::compiled-frame-escaped frame)
1574                  (eq (di:code-location-kind code-location)
1575                      :single-value-return)
1576                  (= (length next) 1)
1577                  (di:code-location= (car next) (adjust-pc)))
1578             (debug::next-code-locations (car next)))
1579            (t
1580             next)))))
1581
1582(defun set-step-breakpoints (frame)
1583  (let ((cl (di:frame-code-location frame)))
1584    (when (di:debug-block-elsewhere-p (di:code-location-debug-block cl))
1585      (error "Cannot step in elsewhere code"))
1586    (let* ((debug::*bad-code-location-types*
1587            (remove :call-site debug::*bad-code-location-types*))
1588           (next (next-code-locations frame cl)))
1589      (cond (next
1590             (let ((steppoints '()))
1591               (flet ((hook (bp-frame bp)
1592                        (signal-breakpoint bp bp-frame)
1593                        (mapc #'di:delete-breakpoint steppoints)))
1594                 (dolist (code-location next)
1595                   (let ((bp (di:make-breakpoint #'hook code-location
1596                                                 :kind :code-location)))
1597                     (di:activate-breakpoint bp)
1598                     (push bp steppoints))))))
1599            (t
1600             (break-on-return frame))))))
1601
1602
1603;; XXX the return values at return breakpoints should be passed to the
1604;; user hooks. debug-int.lisp should be changed to do this cleanly.
1605
1606;;; The sigcontext and the PC for a breakpoint invocation are not
1607;;; passed to user hook functions, but we need them to extract return
1608;;; values. So we advice di::handle-breakpoint and bind the values to
1609;;; special variables.
1610;;;
1611(defvar *breakpoint-sigcontext*)
1612(defvar *breakpoint-pc*)
1613
1614(define-fwrapper bind-breakpoint-sigcontext (offset c sigcontext)
1615  (let ((*breakpoint-sigcontext* sigcontext)
1616        (*breakpoint-pc* offset))
1617    (call-next-function)))
1618(set-fwrappers 'di::handle-breakpoint '())
1619(fwrap 'di::handle-breakpoint #'bind-breakpoint-sigcontext)
1620
1621(defun sigcontext-object (sc index)
1622  "Extract the lisp object in sigcontext SC at offset INDEX."
1623  (kernel:make-lisp-obj (vm:sigcontext-register sc index)))
1624
1625(defun known-return-point-values (sigcontext sc-offsets)
1626  (let ((fp (system:int-sap (vm:sigcontext-register sigcontext
1627                                                    vm::cfp-offset))))
1628    (system:without-gcing
1629     (loop for sc-offset across sc-offsets
1630           collect (di::sub-access-debug-var-slot fp sc-offset sigcontext)))))
1631
1632;;; CMUCL returns the first few values in registers and the rest on
1633;;; the stack. In the multiple value case, the number of values is
1634;;; stored in a dedicated register. The values of the registers can be
1635;;; accessed in the sigcontext for the breakpoint.  There are 3 kinds
1636;;; of return conventions: :single-value-return, :unknown-return, and
1637;;; :known-return.
1638;;;
1639;;; The :single-value-return convention returns the value in a
1640;;; register without setting the nargs registers.
1641;;;
1642;;; The :unknown-return variant is used for multiple values. A
1643;;; :unknown-return point consists actually of 2 breakpoints: one for
1644;;; the single value case and one for the general case.  The single
1645;;; value breakpoint comes vm:single-value-return-byte-offset after
1646;;; the multiple value breakpoint.
1647;;;
1648;;; The :known-return convention is used by local functions.
1649;;; :known-return is currently not supported because we don't know
1650;;; where the values are passed.
1651;;;
1652(defun breakpoint-values (breakpoint)
1653  "Return the list of return values for a return point."
1654  (flet ((1st (sc) (sigcontext-object sc (car vm::register-arg-offsets))))
1655    (let ((sc (locally (declare (optimize (speed 0)))
1656                (alien:sap-alien *breakpoint-sigcontext* (* unix:sigcontext))))
1657          (cl (di:breakpoint-what breakpoint)))
1658      (ecase (di:code-location-kind cl)
1659        (:single-value-return
1660         (list (1st sc)))
1661        (:known-return
1662         (let ((info (di:breakpoint-info breakpoint)))
1663           (if (vectorp info)
1664               (known-return-point-values sc info)
1665               (progn
1666                 ;;(break)
1667                 (list "<<known-return convention not supported>>" info)))))
1668        (:unknown-return
1669         (let ((mv-return-pc (di::compiled-code-location-pc cl)))
1670           (if (= mv-return-pc *breakpoint-pc*)
1671               (mv-function-end-breakpoint-values sc)
1672               (list (1st sc)))))))))
1673
1674;; XXX: di::get-function-end-breakpoint-values takes 2 arguments in
1675;; newer versions of CMUCL (after ~March 2005).
1676(defun mv-function-end-breakpoint-values (sigcontext)
1677  (let ((sym (find-symbol "FUNCTION-END-BREAKPOINT-VALUES/STANDARD" :di)))
1678    (cond (sym (funcall sym sigcontext))
1679          (t (funcall 'di::get-function-end-breakpoint-values sigcontext)))))
1680
1681(defun debug-function-returns (debug-fun)
1682  "Return the return style of DEBUG-FUN."
1683  (let* ((cdfun (di::compiled-debug-function-compiler-debug-fun debug-fun)))
1684    (c::compiled-debug-function-returns cdfun)))
1685
1686(define-condition breakpoint (simple-condition)
1687  ((message :initarg :message :reader breakpoint.message)
1688   (values  :initarg :values  :reader breakpoint.values))
1689  (:report (lambda (c stream) (princ (breakpoint.message c) stream))))
1690
1691(defimplementation condition-extras (condition)
1692  (typecase condition
1693    (breakpoint
1694     ;; pop up the source buffer
1695     `((:show-frame-source 0)))
1696    (t '())))
1697
1698(defun signal-breakpoint (breakpoint frame)
1699  "Signal a breakpoint condition for BREAKPOINT in FRAME.
1700Try to create a informative message."
1701  (flet ((brk (values fstring &rest args)
1702           (let ((msg (apply #'format nil fstring args))
1703                 (debug:*stack-top-hint* frame))
1704             (break 'breakpoint :message msg :values values))))
1705    (with-struct (di::breakpoint- kind what) breakpoint
1706      (case kind
1707        (:code-location
1708         (case (di:code-location-kind what)
1709           ((:single-value-return :known-return :unknown-return)
1710            (let ((values (breakpoint-values breakpoint)))
1711              (brk values "Return value: ~{~S ~}" values)))
1712           (t
1713            #+(or)
1714            (when (eq (di:code-location-kind what) :call-site)
1715              (call-site-function breakpoint frame))
1716            (brk nil "Breakpoint: ~S ~S"
1717                 (di:code-location-kind what)
1718                 (di::compiled-code-location-pc what)))))
1719        (:function-start
1720         (brk nil "Function start breakpoint"))
1721        (t (brk nil "Breakpoint: ~A in ~A" breakpoint frame))))))
1722
1723(defimplementation sldb-break-at-start (fname)
1724  (let ((debug-fun (di:function-debug-function (coerce fname 'function))))
1725    (cond ((not debug-fun)
1726           `(:error ,(format nil "~S has no debug-function" fname)))
1727          (t
1728           (flet ((hook (frame bp &optional args cookie)
1729                    (declare (ignore args cookie))
1730                    (signal-breakpoint bp frame)))
1731             (let ((bp (di:make-breakpoint #'hook debug-fun
1732                                           :kind :function-start)))
1733               (di:activate-breakpoint bp)
1734               `(:ok ,(format nil "Set breakpoint in ~S" fname))))))))
1735
1736(defun frame-cfp (frame)
1737  "Return the Control-Stack-Frame-Pointer for FRAME."
1738  (etypecase frame
1739    (di::compiled-frame (di::frame-pointer frame))
1740    ((or di::interpreted-frame null) -1)))
1741
1742(defun frame-ip (frame)
1743  "Return the (absolute) instruction pointer and the relative pc of FRAME."
1744  (if (not frame)
1745      -1
1746      (let ((debug-fun (di::frame-debug-function frame)))
1747        (etypecase debug-fun
1748          (di::compiled-debug-function
1749           (let* ((code-loc (di:frame-code-location frame))
1750                  (component (di::compiled-debug-function-component debug-fun))
1751                  (pc (di::compiled-code-location-pc code-loc))
1752                  (ip (sys:without-gcing
1753                       (sys:sap-int
1754                        (sys:sap+ (kernel:code-instructions component) pc)))))
1755             (values ip pc)))
1756          (di::interpreted-debug-function -1)
1757          (di::bogus-debug-function
1758           #-x86
1759           (let* ((real (di::frame-real-frame (di::frame-up frame)))
1760                  (fp (di::frame-pointer real)))
1761             ;;#+(or)
1762             (progn
1763               (format *debug-io* "Frame-real-frame = ~S~%" real)
1764               (format *debug-io* "fp = ~S~%" fp)
1765               (format *debug-io* "lra = ~S~%"
1766                       (kernel:stack-ref fp vm::lra-save-offset)))
1767             (values
1768              (sys:int-sap
1769               (- (kernel:get-lisp-obj-address
1770                   (kernel:stack-ref fp vm::lra-save-offset))
1771                  (- (ash vm:function-code-offset vm:word-shift)
1772                     vm:function-pointer-type)))
1773              0))
1774           #+x86
1775           (let ((fp (di::frame-pointer (di:frame-up frame))))
1776             (multiple-value-bind (ra ofp) (di::x86-call-context fp)
1777               (declare (ignore ofp))
1778               (values ra 0))))))))
1779
1780(defun frame-registers (frame)
1781  "Return the lisp registers CSP, CFP, IP, OCFP, LRA for FRAME-NUMBER."
1782  (let* ((cfp (frame-cfp frame))
1783         (csp (frame-cfp (di::frame-up frame)))
1784         (ip (frame-ip frame))
1785         (ocfp (frame-cfp (di::frame-down frame)))
1786         (lra (frame-ip (di::frame-down frame))))
1787    (values csp cfp ip ocfp lra)))
1788
1789(defun print-frame-registers (frame-number)
1790  (let ((frame (di::frame-real-frame (nth-frame frame-number))))
1791    (flet ((fixnum (p) (etypecase p
1792                         (integer p)
1793                         (sys:system-area-pointer (sys:sap-int p)))))
1794      (apply #'format t "~
1795~8X  Stack Pointer
1796~8X  Frame Pointer
1797~8X  Instruction Pointer
1798~8X  Saved Frame Pointer
1799~8X  Saved Instruction Pointer~%" (mapcar #'fixnum
1800                      (multiple-value-list (frame-registers frame)))))))
1801
1802(defvar *gdb-program-name*
1803  (ext:enumerate-search-list (p "path:gdb")
1804    (when (probe-file p)
1805      (return p))))
1806
1807(defimplementation disassemble-frame (frame-number)
1808  (print-frame-registers frame-number)
1809  (terpri)
1810  (let* ((frame (di::frame-real-frame (nth-frame frame-number)))
1811         (debug-fun (di::frame-debug-function frame)))
1812    (etypecase debug-fun
1813      (di::compiled-debug-function
1814       (let* ((component (di::compiled-debug-function-component debug-fun))
1815              (fun (di:debug-function-function debug-fun)))
1816         (if fun
1817             (disassemble fun)
1818             (disassem:disassemble-code-component component))))
1819      (di::bogus-debug-function
1820       (cond ((probe-file *gdb-program-name*)
1821              (let ((ip (sys:sap-int (frame-ip frame))))
1822                (princ (gdb-command "disas 0x~x" ip))))
1823             (t
1824              (format t "~%[Disassembling bogus frames not implemented]")))))))
1825
1826(defmacro with-temporary-file ((stream filename) &body body)
1827  `(call/temporary-file (lambda (,stream ,filename) . ,body)))
1828
1829(defun call/temporary-file (fun)
1830  (let ((name (system::pick-temporary-file-name)))
1831    (unwind-protect
1832         (with-open-file (stream name :direction :output :if-exists :supersede)
1833           (funcall fun stream name))
1834      (delete-file name))))
1835
1836(defun gdb-command (format-string &rest args)
1837  (let ((str (gdb-exec (format nil
1838                               "interpreter-exec mi2 \"attach ~d\"~%~
1839                                interpreter-exec console ~s~%detach"
1840                               (getpid)
1841                               (apply #'format nil format-string args))))
1842        (prompt (format nil
1843                        #-(and darwin x86) "~%^done~%(gdb) ~%"
1844                        #+(and darwin x86)
1845"~%^done,thread-id=\"1\"~%(gdb) ~%")))
1846    (subseq str (+ (or (search prompt str) 0) (length prompt)))))
1847
1848(defun gdb-exec (cmd)
1849  (with-temporary-file (file filename)
1850    (write-string cmd file)
1851    (force-output file)
1852    (let* ((output (make-string-output-stream))
1853           ;; gdb on sparc needs to know the executable to find the
1854           ;; symbols.  Without this, gdb can't disassemble anything.
1855           ;; NOTE: We assume that the first entry in
1856           ;; lisp::*cmucl-lib* is the bin directory where lisp is
1857           ;; located.  If this is not true, we'll have to do
1858           ;; something better to find the lisp executable.
1859           (lisp-path
1860            #+sparc
1861             (list
1862              (namestring
1863               (probe-file
1864                (merge-pathnames "lisp" (car (lisp::parse-unix-search-path
1865                                              lisp::*cmucl-lib*))))))
1866             #-sparc
1867             nil)
1868           (proc (ext:run-program *gdb-program-name*
1869                                  `(,@lisp-path "-batch" "-x" ,filename)
1870                                  :wait t
1871                                  :output output)))
1872      (assert (eq (ext:process-status proc) :exited))
1873      (assert (eq (ext:process-exit-code proc) 0))
1874      (get-output-stream-string output))))
1875
1876(defun foreign-frame-p (frame)
1877  #-x86
1878  (let ((ip (frame-ip frame)))
1879    (and (sys:system-area-pointer-p ip)
1880         (typep (di::frame-debug-function frame) 'di::bogus-debug-function)))
1881  #+x86
1882  (let ((ip (frame-ip frame)))
1883    (and (sys:system-area-pointer-p ip)
1884         (multiple-value-bind (pc code)
1885             (di::compute-lra-data-from-pc ip)
1886           (declare (ignore pc))
1887           (not code)))))
1888
1889(defun foreign-frame-source-location (frame)
1890  (let ((ip (sys:sap-int (frame-ip frame))))
1891    (cond ((probe-file *gdb-program-name*)
1892           (parse-gdb-line-info (gdb-command "info line *0x~x" ip)))
1893          (t `(:error "no srcloc available for ~a" frame)))))
1894
1895;; The output of gdb looks like:
1896;; Line 215 of "../../src/lisp/x86-assem.S"
1897;;    starts at address 0x805318c <Ldone+11>
1898;;    and ends at 0x805318e <Ldone+13>.
1899;; The ../../ are fixed up with the "target:" search list which might
1900;; be wrong sometimes.
1901(defun parse-gdb-line-info (string)
1902  (with-input-from-string (*standard-input* string)
1903    (let ((w1 (read-word)))
1904      (cond ((equal w1 "Line")
1905             (let ((line (read-word)))
1906               (assert (equal (read-word) "of"))
1907               (let* ((file (read-from-string (read-word)))
1908                      (pathname
1909                       (or (probe-file file)
1910                           (probe-file (format nil "target:lisp/~a" file))
1911                           file)))
1912                 (make-location (list :file (unix-truename pathname))
1913                                (list :line (parse-integer line))))))
1914            (t
1915             `(:error ,string))))))
1916
1917(defun read-word (&optional (stream *standard-input*))
1918  (peek-char t stream)
1919  (concatenate 'string (loop until (whitespacep (peek-char nil stream))
1920                             collect (read-char stream))))
1921
1922(defun whitespacep (char)
1923  (member char '(#\space #\newline)))
1924
1925
1926;;;; Inspecting
1927
1928(defconstant +lowtag-symbols+
1929  '(vm:even-fixnum-type
1930    vm:function-pointer-type
1931    vm:other-immediate-0-type
1932    vm:list-pointer-type
1933    vm:odd-fixnum-type
1934    vm:instance-pointer-type
1935    vm:other-immediate-1-type
1936    vm:other-pointer-type)
1937  "Names of the constants that specify type tags.
1938The `symbol-value' of each element is a type tag.")
1939
1940(defconstant +header-type-symbols+
1941  (labels ((suffixp (suffix string)
1942             (and (>= (length string) (length suffix))
1943                  (string= string suffix :start1 (- (length string)
1944                                                    (length suffix)))))
1945           (header-type-symbol-p (x)
1946             (and (suffixp "-TYPE" (symbol-name x))
1947                  (not (member x +lowtag-symbols+))
1948                  (boundp x)
1949                  (typep (symbol-value x) 'fixnum))))
1950    (remove-if-not #'header-type-symbol-p
1951                   (append (apropos-list "-TYPE" "VM")
1952                           (apropos-list "-TYPE" "BIGNUM"))))
1953  "A list of names of the type codes in boxed objects.")
1954
1955(defimplementation describe-primitive-type (object)
1956  (with-output-to-string (*standard-output*)
1957    (let* ((lowtag (kernel:get-lowtag object))
1958           (lowtag-symbol (find lowtag +lowtag-symbols+ :key #'symbol-value)))
1959      (format t "lowtag: ~A" lowtag-symbol)
1960      (when (member lowtag (list vm:other-pointer-type
1961                                 vm:function-pointer-type
1962                                 vm:other-immediate-0-type
1963                                 vm:other-immediate-1-type
1964                                 ))
1965        (let* ((type (kernel:get-type object))
1966               (type-symbol (find type +header-type-symbols+
1967                                  :key #'symbol-value)))
1968          (format t ", type: ~A" type-symbol))))))
1969
1970(defmethod emacs-inspect ((o t))
1971  (cond ((di::indirect-value-cell-p o)
1972         `("Value: " (:value ,(c:value-cell-ref o))))
1973        ((alien::alien-value-p o)
1974         (inspect-alien-value o))
1975	(t
1976         (cmucl-inspect o))))
1977
1978(defun cmucl-inspect (o)
1979  (destructuring-bind (text labeledp . parts) (inspect::describe-parts o)
1980    (list* (format nil "~A~%" text)
1981           (if labeledp
1982               (loop for (label . value) in parts
1983                     append (label-value-line label value))
1984               (loop for value in parts  for i from 0
1985                     append (label-value-line i value))))))
1986
1987(defmethod emacs-inspect ((o function))
1988  (let ((header (kernel:get-type o)))
1989    (cond ((= header vm:function-header-type)
1990           (append (label-value-line*
1991                    ("Self" (kernel:%function-self o))
1992                    ("Next" (kernel:%function-next o))
1993                    ("Name" (kernel:%function-name o))
1994                    ("Arglist" (kernel:%function-arglist o))
1995                    ("Type" (kernel:%function-type o))
1996                    ("Code" (kernel:function-code-header o)))
1997                   (list
1998                    (with-output-to-string (s)
1999                      (disassem:disassemble-function o :stream s)))))
2000          ((= header vm:closure-header-type)
2001           (list* (format nil "~A is a closure.~%" o)
2002                  (append
2003                   (label-value-line "Function" (kernel:%closure-function o))
2004                   `("Environment:" (:newline))
2005                   (loop for i from 0 below (1- (kernel:get-closure-length o))
2006                         append (label-value-line
2007                                 i (kernel:%closure-index-ref o i))))))
2008          ((eval::interpreted-function-p o)
2009           (cmucl-inspect o))
2010          (t
2011           (call-next-method)))))
2012
2013(defmethod emacs-inspect ((o kernel:funcallable-instance))
2014  (append (label-value-line*
2015           (:function (kernel:%funcallable-instance-function o))
2016           (:lexenv  (kernel:%funcallable-instance-lexenv o))
2017           (:layout  (kernel:%funcallable-instance-layout o)))
2018          (cmucl-inspect o)))
2019
2020(defmethod emacs-inspect ((o kernel:code-component))
2021  (append
2022   (label-value-line*
2023    ("code-size" (kernel:%code-code-size o))
2024    ("entry-points" (kernel:%code-entry-points o))
2025    ("debug-info" (kernel:%code-debug-info o))
2026    ("trace-table-offset" (kernel:code-header-ref
2027                           o vm:code-trace-table-offset-slot)))
2028   `("Constants:" (:newline))
2029   (loop for i from vm:code-constants-offset
2030         below (kernel:get-header-data o)
2031         append (label-value-line i (kernel:code-header-ref o i)))
2032   `("Code:"
2033     (:newline)
2034     , (with-output-to-string (*standard-output*)
2035         (cond ((c::compiled-debug-info-p (kernel:%code-debug-info o))
2036                (disassem:disassemble-code-component o))
2037               ((or
2038                 (c::debug-info-p (kernel:%code-debug-info o))
2039                 (consp (kernel:code-header-ref
2040                         o vm:code-trace-table-offset-slot)))
2041                (c:disassem-byte-component o))
2042               (t
2043                (disassem:disassemble-memory
2044                 (disassem::align
2045                  (+ (logandc2 (kernel:get-lisp-obj-address o)
2046                               vm:lowtag-mask)
2047                     (* vm:code-constants-offset vm:word-bytes))
2048                  (ash 1 vm:lowtag-bits))
2049                 (ash (kernel:%code-code-size o) vm:word-shift))))))))
2050
2051(defmethod emacs-inspect ((o kernel:fdefn))
2052  (label-value-line*
2053   ("name" (kernel:fdefn-name o))
2054   ("function" (kernel:fdefn-function o))
2055   ("raw-addr" (sys:sap-ref-32
2056                (sys:int-sap (kernel:get-lisp-obj-address o))
2057                (* vm:fdefn-raw-addr-slot vm:word-bytes)))))
2058
2059#+(or)
2060(defmethod emacs-inspect ((o array))
2061  (if (typep o 'simple-array)
2062      (call-next-method)
2063      (label-value-line*
2064       (:header (describe-primitive-type o))
2065       (:rank (array-rank o))
2066       (:fill-pointer (kernel:%array-fill-pointer o))
2067       (:fill-pointer-p (kernel:%array-fill-pointer-p o))
2068       (:elements (kernel:%array-available-elements o))
2069       (:data (kernel:%array-data-vector o))
2070       (:displacement (kernel:%array-displacement o))
2071       (:displaced-p (kernel:%array-displaced-p o))
2072       (:dimensions (array-dimensions o)))))
2073
2074(defmethod emacs-inspect ((o simple-vector))
2075  (append
2076   (label-value-line*
2077    (:header (describe-primitive-type o))
2078    (:length (c::vector-length o)))
2079   (loop for i below (length o)
2080         append (label-value-line i (aref o i)))))
2081
2082(defun inspect-alien-record (alien)
2083  (with-struct (alien::alien-value- sap type) alien
2084    (with-struct (alien::alien-record-type- kind name fields) type
2085      (append
2086       (label-value-line*
2087        (:sap sap)
2088        (:kind kind)
2089        (:name name))
2090       (loop for field in fields
2091             append (let ((slot (alien::alien-record-field-name field)))
2092                      (declare (optimize (speed 0)))
2093                      (label-value-line slot (alien:slot alien slot))))))))
2094
2095(defun inspect-alien-pointer (alien)
2096  (with-struct (alien::alien-value- sap type) alien
2097    (label-value-line*
2098     (:sap sap)
2099     (:type type)
2100     (:to (alien::deref alien)))))
2101
2102(defun inspect-alien-value (alien)
2103  (typecase (alien::alien-value-type alien)
2104    (alien::alien-record-type (inspect-alien-record alien))
2105    (alien::alien-pointer-type (inspect-alien-pointer alien))
2106    (t (cmucl-inspect alien))))
2107
2108(defimplementation eval-context (obj)
2109  (cond ((typep (class-of obj) 'structure-class)
2110         (let* ((dd (kernel:layout-info (kernel:layout-of obj)))
2111                (slots (kernel:dd-slots dd)))
2112           (list* (cons '*package*
2113                        (symbol-package (if slots
2114                                            (kernel:dsd-name (car slots))
2115                                            (kernel:dd-name dd))))
2116                  (loop for slot in slots collect
2117                        (cons (kernel:dsd-name slot)
2118                              (funcall (kernel:dsd-accessor slot) obj))))))))
2119
2120
2121;;;; Profiling
2122(defimplementation profile (fname)
2123  (eval `(profile:profile ,fname)))
2124
2125(defimplementation unprofile (fname)
2126  (eval `(profile:unprofile ,fname)))
2127
2128(defimplementation unprofile-all ()
2129  (eval `(profile:unprofile))
2130  "All functions unprofiled.")
2131
2132(defimplementation profile-report ()
2133  (eval `(profile:report-time)))
2134
2135(defimplementation profile-reset ()
2136  (eval `(profile:reset-time))
2137  "Reset profiling counters.")
2138
2139(defimplementation profiled-functions ()
2140  profile:*timed-functions*)
2141
2142(defimplementation profile-package (package callers methods)
2143  (profile:profile-all :package package
2144                       :callers-p callers
2145                       :methods methods))
2146
2147
2148;;;; Multiprocessing
2149
2150#+mp
2151(progn
2152  (defimplementation initialize-multiprocessing (continuation)
2153    (mp::init-multi-processing)
2154    (mp:make-process continuation :name "swank")
2155    ;; Threads magic: this never returns! But top-level becomes
2156    ;; available again.
2157    (unless mp::*idle-process*
2158      (mp::startup-idle-and-top-level-loops)))
2159
2160  (defimplementation spawn (fn &key name)
2161    (mp:make-process fn :name (or name "Anonymous")))
2162
2163  (defvar *thread-id-counter* 0)
2164
2165  (defimplementation thread-id (thread)
2166    (or (getf (mp:process-property-list thread) 'id)
2167        (setf (getf (mp:process-property-list thread) 'id)
2168              (incf *thread-id-counter*))))
2169
2170  (defimplementation find-thread (id)
2171    (find id (all-threads)
2172          :key (lambda (p) (getf (mp:process-property-list p) 'id))))
2173
2174  (defimplementation thread-name (thread)
2175    (mp:process-name thread))
2176
2177  (defimplementation thread-status (thread)
2178    (mp:process-whostate thread))
2179
2180  (defimplementation current-thread ()
2181    mp:*current-process*)
2182
2183  (defimplementation all-threads ()
2184    (copy-list mp:*all-processes*))
2185
2186  (defimplementation interrupt-thread (thread fn)
2187    (mp:process-interrupt thread fn))
2188
2189  (defimplementation kill-thread (thread)
2190    (mp:destroy-process thread))
2191
2192  (defvar *mailbox-lock* (mp:make-lock "mailbox lock"))
2193
2194  (defstruct (mailbox (:conc-name mailbox.))
2195    (mutex (mp:make-lock "process mailbox"))
2196    (queue '() :type list))
2197
2198  (defun mailbox (thread)
2199    "Return THREAD's mailbox."
2200    (mp:with-lock-held (*mailbox-lock*)
2201      (or (getf (mp:process-property-list thread) 'mailbox)
2202          (setf (getf (mp:process-property-list thread) 'mailbox)
2203                (make-mailbox)))))
2204
2205  (defimplementation send (thread message)
2206    (check-slime-interrupts)
2207    (let* ((mbox (mailbox thread)))
2208      (mp:with-lock-held ((mailbox.mutex mbox))
2209        (setf (mailbox.queue mbox)
2210              (nconc (mailbox.queue mbox) (list message))))))
2211
2212  (defimplementation receive-if (test &optional timeout)
2213    (let ((mbox (mailbox mp:*current-process*)))
2214      (assert (or (not timeout) (eq timeout t)))
2215      (loop
2216       (check-slime-interrupts)
2217       (mp:with-lock-held ((mailbox.mutex mbox))
2218         (let* ((q (mailbox.queue mbox))
2219                (tail (member-if test q)))
2220           (when tail
2221             (setf (mailbox.queue mbox)
2222                   (nconc (ldiff q tail) (cdr tail)))
2223             (return (car tail)))))
2224       (when (eq timeout t) (return (values nil t)))
2225       (mp:process-wait-with-timeout
2226        "receive-if" 0.5
2227        (lambda () (some test (mailbox.queue mbox)))))))
2228
2229
2230  ) ;; #+mp
2231
2232
2233
2234;;;; GC hooks
2235;;;
2236;;; Display GC messages in the echo area to avoid cluttering the
2237;;; normal output.
2238;;;
2239
2240;; this should probably not be here, but where else?
2241(defun background-message (message)
2242  (swank::background-message message))
2243
2244(defun print-bytes (nbytes &optional stream)
2245  "Print the number NBYTES to STREAM in KB, MB, or GB units."
2246  (let ((names '((0 bytes) (10 kb) (20 mb) (30 gb) (40 tb) (50 eb))))
2247    (multiple-value-bind (power name)
2248	(loop for ((p1 n1) (p2 n2)) on names
2249              while n2 do
2250              (when (<= (expt 2 p1) nbytes (1- (expt 2 p2)))
2251		(return (values p1 n1))))
2252      (cond (name
2253             (format stream "~,1F ~A" (/ nbytes (expt 2 power)) name))
2254            (t
2255             (format stream "~:D bytes" nbytes))))))
2256
2257(defconstant gc-generations 6)
2258
2259#+gencgc
2260(defun generation-stats ()
2261  "Return a string describing the size distribution among the generations."
2262  (let* ((alloc (loop for i below gc-generations
2263                      collect (lisp::gencgc-stats i)))
2264         (sum (coerce (reduce #'+ alloc) 'float)))
2265    (format nil "~{~3F~^/~}"
2266            (mapcar (lambda (size) (/ size sum))
2267                    alloc))))
2268
2269(defvar *gc-start-time* 0)
2270
2271(defun pre-gc-hook (bytes-in-use)
2272  (setq *gc-start-time* (get-internal-real-time))
2273  (let ((msg (format nil "[Commencing GC with ~A in use.]"
2274                     (print-bytes bytes-in-use))))
2275    (background-message msg)))
2276
2277(defun post-gc-hook (bytes-retained bytes-freed trigger)
2278  (declare (ignore trigger))
2279  (let* ((seconds (/ (- (get-internal-real-time) *gc-start-time*)
2280                     internal-time-units-per-second))
2281         (msg (format nil "[GC done. ~A freed  ~A retained  ~A  ~4F sec]"
2282                     (print-bytes bytes-freed)
2283                     (print-bytes bytes-retained)
2284                     #+gencgc(generation-stats)
2285                     #-gencgc""
2286                     seconds)))
2287    (background-message msg)))
2288
2289(defun install-gc-hooks ()
2290  (setq ext:*gc-notify-before* #'pre-gc-hook)
2291  (setq ext:*gc-notify-after* #'post-gc-hook))
2292
2293(defun remove-gc-hooks ()
2294  (setq ext:*gc-notify-before* #'lisp::default-gc-notify-before)
2295  (setq ext:*gc-notify-after* #'lisp::default-gc-notify-after))
2296
2297(defvar *install-gc-hooks* t
2298  "If non-nil install GC hooks")
2299
2300(defimplementation emacs-connected ()
2301  (when *install-gc-hooks*
2302    (install-gc-hooks)))
2303
2304;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2305;;Trace implementations
2306;;In CMUCL, we have:
2307;; (trace <name>)
2308;; (trace (method <name> <qualifier>? (<specializer>+)))
2309;; (trace :methods t '<name>) ;;to trace all methods of the gf <name>
2310;; <name> can be a normal name or a (setf name)
2311
2312(defun tracedp (spec)
2313  (member spec (eval '(trace)) :test #'equal))
2314
2315(defun toggle-trace-aux (spec &rest options)
2316  (cond ((tracedp spec)
2317         (eval `(untrace ,spec))
2318         (format nil "~S is now untraced." spec))
2319        (t
2320         (eval `(trace ,spec ,@options))
2321         (format nil "~S is now traced." spec))))
2322
2323(defimplementation toggle-trace (spec)
2324  (ecase (car spec)
2325    ((setf)
2326     (toggle-trace-aux spec))
2327    ((:defgeneric)
2328     (let ((name (second spec)))
2329       (toggle-trace-aux name :methods name)))
2330    ((:defmethod)
2331     (cond ((fboundp `(method ,@(cdr spec)))
2332            (toggle-trace-aux `(method ,(cdr spec))))
2333           ;; Man, is this ugly
2334           ((fboundp `(pcl::fast-method ,@(cdr spec)))
2335            (toggle-trace-aux `(pcl::fast-method ,@(cdr spec))))
2336           (t
2337            (error 'undefined-function :name (cdr spec)))))
2338    ((:call)
2339     (destructuring-bind (caller callee) (cdr spec)
2340       (toggle-trace-aux (process-fspec callee)
2341                         :wherein (list (process-fspec caller)))))
2342    ;; doesn't work properly
2343    ;; ((:labels :flet) (toggle-trace-aux (process-fspec spec)))
2344    ))
2345
2346(defun process-fspec (fspec)
2347  (cond ((consp fspec)
2348         (ecase (first fspec)
2349           ((:defun :defgeneric) (second fspec))
2350           ((:defmethod)
2351            `(method ,(second fspec) ,@(third fspec) ,(fourth fspec)))
2352           ((:labels) `(labels ,(third fspec) ,(process-fspec (second fspec))))
2353           ((:flet) `(flet ,(third fspec) ,(process-fspec (second fspec))))))
2354        (t
2355         fspec)))
2356
2357;;; Weak datastructures
2358
2359(defimplementation make-weak-key-hash-table (&rest args)
2360  (apply #'make-hash-table :weak-p t args))
2361
2362
2363;;; Save image
2364
2365(defimplementation save-image (filename &optional restart-function)
2366  (multiple-value-bind (pid error) (unix:unix-fork)
2367    (when (not pid) (error "fork: ~A" (unix:get-unix-error-msg error)))
2368    (cond ((= pid 0)
2369           (apply #'ext:save-lisp
2370                  filename
2371                  (if restart-function
2372                      `(:init-function ,restart-function))))
2373          (t
2374           (let ((status (waitpid pid)))
2375             (destructuring-bind (&key exited? status &allow-other-keys) status
2376               (assert (and exited? (equal status 0)) ()
2377                       "Invalid exit status: ~a" status)))))))
2378
2379(defun waitpid (pid)
2380  (alien:with-alien ((status c-call:int))
2381    (let ((code (alien:alien-funcall
2382                 (alien:extern-alien
2383                  waitpid (alien:function c-call:int c-call:int
2384                                          (* c-call:int) c-call:int))
2385                 pid (alien:addr status) 0)))
2386      (cond ((= code -1) (error "waitpid: ~A" (unix:get-unix-error-msg)))
2387            (t (assert (= code pid))
2388               (decode-wait-status status))))))
2389
2390(defun decode-wait-status (status)
2391  (let ((output (with-output-to-string (s)
2392                  (call-program (list (process-status-program)
2393                                      (format nil "~d" status))
2394                                :output s))))
2395    (read-from-string output)))
2396
2397(defun call-program (args &key output)
2398  (destructuring-bind (program &rest args) args
2399    (let ((process (ext:run-program program args :output output)))
2400      (when (not program) (error "fork failed"))
2401      (unless (and (eq (ext:process-status process) :exited)
2402                   (= (ext:process-exit-code process) 0))
2403        (error "Non-zero exit status")))))
2404
2405(defvar *process-status-program* nil)
2406
2407(defun process-status-program ()
2408  (or *process-status-program*
2409      (setq *process-status-program*
2410            (compile-process-status-program))))
2411
2412(defun compile-process-status-program ()
2413  (let ((infile (system::pick-temporary-file-name
2414                 "/tmp/process-status~d~c.c")))
2415    (with-open-file (stream infile :direction :output :if-exists :supersede)
2416      (format stream "
2417#include <stdio.h>
2418#include <stdlib.h>
2419#include <sys/types.h>
2420#include <sys/wait.h>
2421#include <assert.h>
2422
2423#define FLAG(value) (value ? \"t\" : \"nil\")
2424
2425int main (int argc, char** argv) {
2426  assert (argc == 2);
2427  {
2428    char* endptr = NULL;
2429    char* arg = argv[1];
2430    long int status = strtol (arg, &endptr, 10);
2431    assert (endptr != arg && *endptr == '\\0');
2432    printf (\"(:exited? %s :status %d :signal? %s :signal %d :coredump? %s\"
2433            \" :stopped? %s :stopsig %d)\\n\",
2434            FLAG(WIFEXITED(status)), WEXITSTATUS(status),
2435            FLAG(WIFSIGNALED(status)), WTERMSIG(status),
2436            FLAG(WCOREDUMP(status)),
2437            FLAG(WIFSTOPPED(status)), WSTOPSIG(status));
2438    fflush (NULL);
2439    return 0;
2440  }
2441}
2442")
2443      (finish-output stream))
2444    (let* ((outfile (system::pick-temporary-file-name))
2445           (args (list "cc" "-o" outfile infile)))
2446      (warn "Running cc: ~{~a ~}~%" args)
2447      (call-program args :output t)
2448      (delete-file infile)
2449      outfile)))
2450
2451;; FIXME: lisp:unicode-complete introduced in version 20d.
2452#+#.(swank/backend:with-symbol 'unicode-complete 'lisp)
2453(defun match-semi-standard (prefix matchp)
2454  ;; Handle the CMUCL's short character names.
2455  (loop for name in lisp::char-name-alist
2456     when (funcall matchp prefix (car name))
2457     collect (car name)))
2458
2459#+#.(swank/backend:with-symbol 'unicode-complete 'lisp)
2460(defimplementation character-completion-set (prefix matchp)
2461  (let ((names (lisp::unicode-complete prefix)))
2462    ;; Match prefix against semistandard names.  If there's a match,
2463    ;; add it to our list of matches.
2464    (let ((semi-standard (match-semi-standard prefix matchp)))
2465      (when semi-standard
2466        (setf names (append semi-standard names))))
2467    (setf names (mapcar #'string-capitalize names))
2468    (loop for n in names
2469       when (funcall matchp prefix n)
2470       collect n)))
2471